Compiler-Interpreter.st 14 KB

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