Compiler-Interpreter.st 13 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622
  1. Smalltalk current createPackage: 'Compiler-Interpreter'!
  2. NodeVisitor subclass: #AIContext
  3. instanceVariableNames: 'outerContext pc locals method'
  4. package: 'Compiler-Interpreter'!
  5. !AIContext commentStamp!
  6. AIContext is like a `MethodContext`, used by the `ASTInterpreter`.
  7. Unlike a `MethodContext`, it is not read-only.
  8. When debugging, `AIContext` instances are created by copying the current `MethodContext` (thisContext)!
  9. !AIContext methodsFor: 'accessing'!
  10. localAt: aString
  11. ^ self locals at: aString ifAbsent: [ nil ]
  12. !
  13. localAt: aString put: anObject
  14. self locals at: aString put: anObject
  15. !
  16. locals
  17. locals ifNil: [ self initializeLocals ].
  18. ^ locals
  19. !
  20. method
  21. ^ method
  22. !
  23. method: aCompiledMethod
  24. method := aCompiledMethod
  25. !
  26. outerContext
  27. ^ outerContext
  28. !
  29. outerContext: anAIContext
  30. outerContext := anAIContext
  31. !
  32. pc
  33. ^ pc ifNil: [ pc := 0 ]
  34. !
  35. pc: anInteger
  36. pc := anInteger
  37. !
  38. receiver
  39. ^ self localAt: 'self'
  40. !
  41. receiver: anObject
  42. self localAt: 'self' put: anObject
  43. !
  44. selector
  45. ^ self method
  46. ifNotNil: [ self method selector ]
  47. ! !
  48. !AIContext methodsFor: 'initialization'!
  49. initializeFromMethodContext: aMethodContext
  50. self pc: aMethodContext pc.
  51. self receiver: aMethodContext receiver.
  52. self method: aMethodContext method.
  53. aMethodContext outerContext ifNotNil: [
  54. self outerContext: (self class fromMethodContext: aMethodContext outerContext) ].
  55. aMethodContext locals keysAndValuesDo: [ :key :value |
  56. self locals at: key put: value ]
  57. !
  58. initializeLocals
  59. locals := Dictionary new.
  60. locals at: 'thisContext' put: self.
  61. ! !
  62. !AIContext class methodsFor: 'instance creation'!
  63. fromMethodContext: aMethodContext
  64. ^ self new
  65. initializeFromMethodContext: aMethodContext;
  66. yourself
  67. ! !
  68. Object subclass: #ASTDebugger
  69. instanceVariableNames: 'interpreter context'
  70. package: 'Compiler-Interpreter'!
  71. !ASTDebugger commentStamp!
  72. ASTDebugger is a debugger to Amber.
  73. It uses an AST interpreter to step through the code.
  74. ASTDebugger instances are created from a `MethodContext` with `ASTDebugger class >> context:`.
  75. They hold an `AIContext` instance internally, recursive copy of the `MethodContext`.
  76. Use the methods of the 'stepping' protocol to do stepping.!
  77. !ASTDebugger methodsFor: 'accessing'!
  78. context
  79. ^ context
  80. !
  81. context: aContext
  82. context := AIContext new.
  83. !
  84. interpreter
  85. ^ interpreter ifNil: [ interpreter := self defaultInterpreterClass new ]
  86. !
  87. interpreter: anInterpreter
  88. interpreter := anInterpreter
  89. !
  90. method
  91. ^ self context method
  92. ! !
  93. !ASTDebugger methodsFor: 'defaults'!
  94. defaultInterpreterClass
  95. ^ ASTSteppingInterpreter
  96. ! !
  97. !ASTDebugger methodsFor: 'initialization'!
  98. buildAST
  99. "Build the AST tree from the method source code.
  100. The AST is annotated with a SemanticAnalyzer,
  101. to know the semantics and bindings of each node needed for later debugging"
  102. | ast |
  103. ast := Smalltalk current parse: self method source.
  104. (SemanticAnalyzer on: self context receiver class)
  105. visit: ast.
  106. ^ ast
  107. !
  108. initializeInterpreter
  109. self interpreter interpret: self buildAST nodes first
  110. !
  111. initializeWithContext: aMethodContext
  112. "TODO: do we need to handle block contexts?"
  113. self context: (AIContext fromMethodContext: aMethodContext).
  114. self initializeInterpreter
  115. ! !
  116. !ASTDebugger methodsFor: 'stepping'!
  117. restart
  118. self shouldBeImplemented
  119. !
  120. resume
  121. self shouldBeImplemented
  122. !
  123. step
  124. "The ASTSteppingInterpreter stops at each node interpretation.
  125. One step will interpret nodes until:
  126. - we get at the end
  127. - the next node is a stepping node (send, assignment, etc.)"
  128. [ (self interpreter nextNode notNil and: [ self interpreter nextNode stopOnStepping ])
  129. or: [ self interpreter atEnd not ] ]
  130. whileFalse: [
  131. self interpreter step.
  132. self step ]
  133. !
  134. stepInto
  135. self shouldBeImplemented
  136. !
  137. stepOver
  138. self step
  139. ! !
  140. !ASTDebugger class methodsFor: 'instance creation'!
  141. context: aMethodContext
  142. ^ self new
  143. initializeWithContext: aMethodContext;
  144. yourself
  145. ! !
  146. Object subclass: #ASTInterpreter
  147. instanceVariableNames: 'currentNode context shouldReturn result'
  148. package: 'Compiler-Interpreter'!
  149. !ASTInterpreter commentStamp!
  150. ASTIntepreter is like a `NodeVisitor`, interpreting nodes one after each other.
  151. It is built using Continuation Passing Style for stepping purposes.
  152. Usage example:
  153. | ast interpreter |
  154. ast := Smalltalk current parse: 'foo 1+2+4'.
  155. (SemanticAnalyzer on: Object) visit: ast.
  156. ASTInterpreter new
  157. interpret: ast nodes first;
  158. result "Answers 7"!
  159. !ASTInterpreter methodsFor: 'accessing'!
  160. context
  161. ^ context ifNil: [ context := AIContext new ]
  162. !
  163. context: anAIContext
  164. context := anAIContext
  165. !
  166. currentNode
  167. ^ currentNode
  168. !
  169. result
  170. ^ result
  171. ! !
  172. !ASTInterpreter methodsFor: 'initialization'!
  173. initialize
  174. super initialize.
  175. shouldReturn := false
  176. ! !
  177. !ASTInterpreter methodsFor: 'interpreting'!
  178. interpret: aNode
  179. shouldReturn := false.
  180. self interpret: aNode continue: [ :value |
  181. result := value ]
  182. !
  183. interpret: aNode continue: aBlock
  184. shouldReturn ifTrue: [ ^ self ].
  185. aNode isNode
  186. ifTrue: [
  187. currentNode := aNode.
  188. self interpretNode: aNode continue: [ :value |
  189. self continue: aBlock value: value ] ]
  190. ifFalse: [ self continue: aBlock value: aNode ]
  191. !
  192. interpretAssignmentNode: aNode continue: aBlock
  193. self interpret: aNode right continue: [ :value |
  194. self
  195. continue: aBlock
  196. value: (self assign: aNode left to: value) ]
  197. !
  198. interpretBlockNode: aNode continue: aBlock
  199. self
  200. continue: aBlock
  201. value: [
  202. self withBlockContext: [
  203. self interpret: aNode nodes first; result ] ]
  204. !
  205. interpretBlockSequenceNode: aNode continue: aBlock
  206. self interpretSequenceNode: aNode continue: aBlock
  207. !
  208. interpretCascadeNode: aNode continue: aBlock
  209. "TODO: Handle super sends"
  210. self interpret: aNode receiver continue: [ :receiver |
  211. "Only interpret the receiver once"
  212. aNode nodes do: [ :each | each receiver: receiver ].
  213. self
  214. interpretAll: aNode nodes allButLast
  215. continue: [
  216. self
  217. interpret: aNode nodes last
  218. continue: [ :val | self continue: aBlock value: val ] ] ]
  219. !
  220. interpretClassReferenceNode: aNode continue: aBlock
  221. self continue: aBlock value: (Smalltalk current at: aNode value)
  222. !
  223. interpretDynamicArrayNode: aNode continue: aBlock
  224. self interpretAll: aNode nodes continue: [ :array |
  225. self
  226. continue: aBlock
  227. value: array ]
  228. !
  229. interpretDynamicDictionaryNode: aNode continue: aBlock
  230. self interpretAll: aNode nodes continue: [ :array | | hashedCollection |
  231. hashedCollection := HashedCollection new.
  232. array do: [ :each | hashedCollection add: each ].
  233. self
  234. continue: aBlock
  235. value: hashedCollection ]
  236. !
  237. interpretJSStatementNode: aNode continue: aBlock
  238. shouldReturn := true.
  239. self continue: aBlock value: (self eval: aNode source)
  240. !
  241. interpretMethodNode: aNode continue: aBlock
  242. self interpretAll: aNode nodes continue: [ :array |
  243. self continue: aBlock value: array first ]
  244. !
  245. interpretNode: aNode continue: aBlock
  246. aNode interpreter: self continue: aBlock
  247. !
  248. interpretReturnNode: aNode continue: aBlock
  249. self interpret: aNode nodes first continue: [ :value |
  250. shouldReturn := true.
  251. self continue: aBlock value: value ]
  252. !
  253. interpretSendNode: aNode continue: aBlock
  254. "TODO: Handle super sends"
  255. self interpret: aNode receiver continue: [ :receiver |
  256. self interpretAll: aNode arguments continue: [ :args |
  257. self
  258. messageFromSendNode: aNode
  259. arguments: args
  260. do: [ :message |
  261. self context pc: self context pc + 1.
  262. self
  263. continue: aBlock
  264. value: (message sendTo: receiver) ] ] ]
  265. !
  266. interpretSequenceNode: aNode continue: aBlock
  267. self interpretAll: aNode nodes continue: [ :array |
  268. self continue: aBlock value: array last ]
  269. !
  270. interpretValueNode: aNode continue: aBlock
  271. self continue: aBlock value: aNode value
  272. !
  273. interpretVariableNode: aNode continue: aBlock
  274. self
  275. continue: aBlock
  276. value: (aNode binding isInstanceVar
  277. ifTrue: [ self context receiver instVarAt: aNode value ]
  278. ifFalse: [ self context localAt: aNode value ])
  279. ! !
  280. !ASTInterpreter methodsFor: 'private'!
  281. assign: aNode to: anObject
  282. ^ aNode binding isInstanceVar
  283. ifTrue: [ self context receiver instVarAt: aNode value put: anObject ]
  284. ifFalse: [ self context localAt: aNode value put: anObject ]
  285. !
  286. continue: aBlock value: anObject
  287. result := anObject.
  288. aBlock value: anObject
  289. !
  290. eval: aString
  291. "Evaluate aString as JS source inside an JS function.
  292. aString is not sandboxed."
  293. | source function |
  294. source := String streamContents: [ :str |
  295. str nextPutAll: '(function('.
  296. self context locals keys
  297. do: [ :each | str nextPutAll: each ]
  298. separatedBy: [ str nextPutAll: ',' ].
  299. str
  300. nextPutAll: '){ return (function() {';
  301. nextPutAll: aString;
  302. nextPutAll: '})() })' ].
  303. function := Compiler new eval: source.
  304. ^ function valueWithPossibleArguments: self context locals values
  305. !
  306. interpretAll: aCollection continue: aBlock
  307. self
  308. interpretAll: aCollection
  309. continue: aBlock
  310. result: OrderedCollection new
  311. !
  312. interpretAll: nodes continue: aBlock result: aCollection
  313. nodes isEmpty
  314. ifTrue: [ self continue: aBlock value: aCollection ]
  315. ifFalse: [
  316. self interpret: nodes first continue: [:value |
  317. self
  318. interpretAll: nodes allButFirst
  319. continue: aBlock
  320. result: aCollection, { value } ] ]
  321. !
  322. messageFromSendNode: aSendNode arguments: aCollection do: aBlock
  323. self
  324. continue: aBlock
  325. value: (Message new
  326. selector: aSendNode selector;
  327. arguments: aCollection;
  328. yourself)
  329. !
  330. withBlockContext: aBlock
  331. "Evaluate aBlock with a BlockContext:
  332. - a context is pushed before aBlock evaluation.
  333. - the context is poped after aBlock evaluation
  334. - the result of aBlock evaluation is answered"
  335. | blockResult |
  336. self context: (AIContext new
  337. outerContext: self context;
  338. yourself).
  339. blockResult := aBlock value.
  340. self context: self context outerContext.
  341. ^ blockResult
  342. ! !
  343. !ASTInterpreter methodsFor: 'testing'!
  344. shouldReturn
  345. ^ shouldReturn ifNil: [ false ]
  346. ! !
  347. ASTInterpreter subclass: #ASTSteppingInterpreter
  348. instanceVariableNames: 'continuation nextNode'
  349. package: 'Compiler-Interpreter'!
  350. !ASTSteppingInterpreter commentStamp!
  351. ASTSteppingInterpreter is an interpreter with stepping capabilities.
  352. Use `#step` to actually interpret the next node.
  353. Usage example:
  354. | ast interpreter |
  355. ast := Smalltalk current parse: 'foo 1+2+4'.
  356. (SemanticAnalyzer on: Object) visit: ast.
  357. interpreter := ASTSteppingInterpreter new
  358. interpret: ast nodes first;
  359. yourself.
  360. debugger step; step.
  361. debugger step; step.
  362. debugger result."Answers 1"
  363. debugger step.
  364. debugger result. "Answers 3"
  365. debugger step.
  366. debugger result. "Answers 7"!
  367. !ASTSteppingInterpreter methodsFor: 'accessing'!
  368. nextNode
  369. ^ nextNode
  370. ! !
  371. !ASTSteppingInterpreter methodsFor: 'initialization'!
  372. initialize
  373. super initialize.
  374. continuation := []
  375. ! !
  376. !ASTSteppingInterpreter methodsFor: 'interpreting'!
  377. interpret: aNode continue: aBlock
  378. nextNode := aNode.
  379. continuation := [
  380. super interpret: aNode continue: aBlock ]
  381. ! !
  382. !ASTSteppingInterpreter methodsFor: 'stepping'!
  383. step
  384. continuation value
  385. ! !
  386. !ASTSteppingInterpreter methodsFor: 'testing'!
  387. atEnd
  388. ^ self shouldReturn or: [ self nextNode == self currentNode ]
  389. ! !
  390. !Node methodsFor: '*Compiler-Interpreter'!
  391. interpreter: anInterpreter continue: aBlock
  392. ^ anInterpreter interpretNode: self continue: aBlock
  393. !
  394. isSteppingNode
  395. ^ false
  396. ! !
  397. !AssignmentNode methodsFor: '*Compiler-Interpreter'!
  398. interpreter: anInterpreter continue: aBlock
  399. ^ anInterpreter interpretAssignmentNode: self continue: aBlock
  400. !
  401. isSteppingNode
  402. ^ true
  403. ! !
  404. !BlockNode methodsFor: '*Compiler-Interpreter'!
  405. interpreter: anInterpreter continue: aBlock
  406. ^ anInterpreter interpretBlockNode: self continue: aBlock
  407. !
  408. isSteppingNode
  409. ^ true
  410. ! !
  411. !CascadeNode methodsFor: '*Compiler-Interpreter'!
  412. interpreter: anInterpreter continue: aBlock
  413. ^ anInterpreter interpretCascadeNode: self continue: aBlock
  414. ! !
  415. !DynamicArrayNode methodsFor: '*Compiler-Interpreter'!
  416. interpreter: anInterpreter continue: aBlock
  417. ^ anInterpreter interpretDynamicArrayNode: self continue: aBlock
  418. !
  419. isSteppingNode
  420. ^ true
  421. ! !
  422. !DynamicDictionaryNode methodsFor: '*Compiler-Interpreter'!
  423. interpreter: anInterpreter continue: aBlock
  424. ^ anInterpreter interpretDynamicDictionaryNode: self continue: aBlock
  425. !
  426. isSteppingNode
  427. ^ true
  428. ! !
  429. !JSStatementNode methodsFor: '*Compiler-Interpreter'!
  430. interpreter: anInterpreter continue: aBlock
  431. ^ anInterpreter interpretJSStatementNode: self continue: aBlock
  432. !
  433. isSteppingNode
  434. ^ true
  435. ! !
  436. !MethodNode methodsFor: '*Compiler-Interpreter'!
  437. interpreter: anInterpreter continue: aBlock
  438. ^ anInterpreter interpretMethodNode: self continue: aBlock
  439. ! !
  440. !ReturnNode methodsFor: '*Compiler-Interpreter'!
  441. interpreter: anInterpreter continue: aBlock
  442. ^ anInterpreter interpretReturnNode: self continue: aBlock
  443. ! !
  444. !SendNode methodsFor: '*Compiler-Interpreter'!
  445. interpreter: anInterpreter continue: aBlock
  446. ^ anInterpreter interpretSendNode: self continue: aBlock
  447. !
  448. isSteppingNode
  449. ^ true
  450. ! !
  451. !SequenceNode methodsFor: '*Compiler-Interpreter'!
  452. interpreter: anInterpreter continue: aBlock
  453. ^ anInterpreter interpretSequenceNode: self continue: aBlock
  454. ! !
  455. !BlockSequenceNode methodsFor: '*Compiler-Interpreter'!
  456. interpreter: anInterpreter continue: aBlock
  457. ^ anInterpreter interpretBlockSequenceNode: self continue: aBlock
  458. ! !
  459. !ValueNode methodsFor: '*Compiler-Interpreter'!
  460. interpreter: anInterpreter continue: aBlock
  461. ^ anInterpreter interpretValueNode: self continue: aBlock
  462. ! !
  463. !VariableNode methodsFor: '*Compiler-Interpreter'!
  464. interpreter: anInterpreter continue: aBlock
  465. ^ anInterpreter interpretVariableNode: self continue: aBlock
  466. ! !
  467. !ClassReferenceNode methodsFor: '*Compiler-Interpreter'!
  468. interpreter: anInterpreter continue: aBlock
  469. ^ anInterpreter interpretClassReferenceNode: self continue: aBlock
  470. ! !