Compiler-Inlining.st 16 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641
  1. Smalltalk createPackage: 'Compiler-Inlining'!
  2. IRAssignment subclass: #IRInlinedAssignment
  3. instanceVariableNames: ''
  4. package: 'Compiler-Inlining'!
  5. !IRInlinedAssignment commentStamp!
  6. I represent an inlined assignment instruction.!
  7. !IRInlinedAssignment methodsFor: 'testing'!
  8. isInlined
  9. ^ true
  10. ! !
  11. !IRInlinedAssignment methodsFor: 'visiting'!
  12. acceptDagVisitor: aVisitor
  13. ^ aVisitor visitIRInlinedAssignment: self
  14. ! !
  15. IRClosure subclass: #IRInlinedClosure
  16. instanceVariableNames: ''
  17. package: 'Compiler-Inlining'!
  18. !IRInlinedClosure commentStamp!
  19. I represent an inlined closure instruction.!
  20. !IRInlinedClosure methodsFor: 'testing'!
  21. isInlined
  22. ^ true
  23. ! !
  24. !IRInlinedClosure methodsFor: 'visiting'!
  25. acceptDagVisitor: aVisitor
  26. aVisitor visitIRInlinedClosure: self
  27. ! !
  28. IRReturn subclass: #IRInlinedReturn
  29. instanceVariableNames: ''
  30. package: 'Compiler-Inlining'!
  31. !IRInlinedReturn commentStamp!
  32. I represent an inlined local return instruction.!
  33. !IRInlinedReturn methodsFor: 'testing'!
  34. isInlined
  35. ^ true
  36. ! !
  37. !IRInlinedReturn methodsFor: 'visiting'!
  38. acceptDagVisitor: aVisitor
  39. ^ aVisitor visitIRInlinedReturn: self
  40. ! !
  41. IRSend subclass: #IRInlinedSend
  42. instanceVariableNames: ''
  43. package: 'Compiler-Inlining'!
  44. !IRInlinedSend commentStamp!
  45. I am the abstract super class of inlined message send instructions.!
  46. !IRInlinedSend methodsFor: 'accessing'!
  47. internalVariables
  48. "Answer a collection of internal variables required
  49. to perform the inlining"
  50. ^ #()
  51. ! !
  52. !IRInlinedSend methodsFor: 'testing'!
  53. isInlined
  54. ^ true
  55. ! !
  56. !IRInlinedSend methodsFor: 'visiting'!
  57. acceptDagVisitor: aVisitor
  58. aVisitor visitInlinedSend: self
  59. ! !
  60. IRInlinedSend subclass: #IRInlinedIfFalse
  61. instanceVariableNames: ''
  62. package: 'Compiler-Inlining'!
  63. !IRInlinedIfFalse commentStamp!
  64. I represent an inlined `#ifFalse:` message send instruction.!
  65. !IRInlinedIfFalse methodsFor: 'visiting'!
  66. acceptDagVisitor: aVisitor
  67. aVisitor visitIRInlinedIfFalse: self
  68. ! !
  69. IRInlinedSend subclass: #IRInlinedIfNilIfNotNil
  70. instanceVariableNames: ''
  71. package: 'Compiler-Inlining'!
  72. !IRInlinedIfNilIfNotNil commentStamp!
  73. I represent an inlined `#ifNil:ifNotNil:` message send instruction.!
  74. !IRInlinedIfNilIfNotNil methodsFor: 'accessing'!
  75. internalVariables
  76. ^ Array with: self receiverInternalVariable
  77. !
  78. receiverInternalVariable
  79. ^ IRVariable new
  80. variable: (AliasVar new name: self receiverInternalVariableName);
  81. yourself.
  82. !
  83. receiverInternalVariableName
  84. ^ '$receiver'
  85. ! !
  86. !IRInlinedIfNilIfNotNil methodsFor: 'visiting'!
  87. acceptDagVisitor: aVisitor
  88. aVisitor visitIRInlinedIfNilIfNotNil: self
  89. ! !
  90. IRInlinedSend subclass: #IRInlinedIfTrue
  91. instanceVariableNames: ''
  92. package: 'Compiler-Inlining'!
  93. !IRInlinedIfTrue commentStamp!
  94. I represent an inlined `#ifTrue:` message send instruction.!
  95. !IRInlinedIfTrue methodsFor: 'visiting'!
  96. acceptDagVisitor: aVisitor
  97. aVisitor visitIRInlinedIfTrue: self
  98. ! !
  99. IRInlinedSend subclass: #IRInlinedIfTrueIfFalse
  100. instanceVariableNames: ''
  101. package: 'Compiler-Inlining'!
  102. !IRInlinedIfTrueIfFalse commentStamp!
  103. I represent an inlined `#ifTrue:ifFalse:` message send instruction.!
  104. !IRInlinedIfTrueIfFalse methodsFor: 'visiting'!
  105. acceptDagVisitor: aVisitor
  106. aVisitor visitIRInlinedIfTrueIfFalse: self
  107. ! !
  108. IRBlockSequence subclass: #IRInlinedSequence
  109. instanceVariableNames: ''
  110. package: 'Compiler-Inlining'!
  111. !IRInlinedSequence commentStamp!
  112. I represent a (block) sequence inside an inlined closure instruction (instance of `IRInlinedClosure`).!
  113. !IRInlinedSequence methodsFor: 'testing'!
  114. isInlined
  115. ^ true
  116. ! !
  117. !IRInlinedSequence methodsFor: 'visiting'!
  118. acceptDagVisitor: aVisitor
  119. aVisitor visitIRInlinedSequence: self
  120. ! !
  121. IRVisitor subclass: #IRInliner
  122. instanceVariableNames: ''
  123. package: 'Compiler-Inlining'!
  124. !IRInliner commentStamp!
  125. I visit an IR tree, inlining message sends and block closures.
  126. Message selectors that can be inlined are answered by `IRSendInliner >> #inlinedSelectors`!
  127. !IRInliner methodsFor: 'factory'!
  128. assignmentInliner
  129. ^ IRAssignmentInliner new
  130. translator: self;
  131. yourself
  132. !
  133. returnInliner
  134. ^ IRReturnInliner new
  135. translator: self;
  136. yourself
  137. !
  138. sendInliner
  139. ^ IRSendInliner new
  140. translator: self;
  141. yourself
  142. ! !
  143. !IRInliner methodsFor: 'testing'!
  144. shouldInlineAssignment: anIRAssignment
  145. ^ anIRAssignment isInlined not and: [
  146. anIRAssignment right isSend and: [
  147. self shouldInlineSend: anIRAssignment right ]]
  148. !
  149. shouldInlineReturn: anIRReturn
  150. ^ anIRReturn isInlined not and: [
  151. anIRReturn expression isSend and: [
  152. self shouldInlineSend: anIRReturn expression ]]
  153. !
  154. shouldInlineSend: anIRSend
  155. ^ anIRSend isInlined not and: [
  156. IRSendInliner shouldInline: anIRSend ]
  157. ! !
  158. !IRInliner methodsFor: 'visiting'!
  159. transformNonLocalReturn: anIRNonLocalReturn
  160. "Replace a non local return into a local return"
  161. | localReturn |
  162. anIRNonLocalReturn scope canInlineNonLocalReturns ifTrue: [
  163. anIRNonLocalReturn scope methodScope removeNonLocalReturn: anIRNonLocalReturn scope.
  164. localReturn := IRReturn new
  165. scope: anIRNonLocalReturn scope;
  166. yourself.
  167. anIRNonLocalReturn dagChildren do: [ :each |
  168. localReturn add: each ].
  169. anIRNonLocalReturn replaceWith: localReturn.
  170. ^ localReturn ].
  171. ^ super visitIRNonLocalReturn: anIRNonLocalReturn
  172. !
  173. visitIRAssignment: anIRAssignment
  174. ^ (self shouldInlineAssignment: anIRAssignment)
  175. ifTrue: [ self assignmentInliner inlineAssignment: anIRAssignment ]
  176. ifFalse: [ super visitIRAssignment: anIRAssignment ]
  177. !
  178. visitIRNonLocalReturn: anIRNonLocalReturn
  179. ^ self transformNonLocalReturn: anIRNonLocalReturn
  180. !
  181. visitIRReturn: anIRReturn
  182. ^ (self shouldInlineReturn: anIRReturn)
  183. ifTrue: [ self returnInliner inlineReturn: anIRReturn ]
  184. ifFalse: [ super visitIRReturn: anIRReturn ]
  185. !
  186. visitIRSend: anIRSend
  187. ^ (self shouldInlineSend: anIRSend)
  188. ifTrue: [ self sendInliner inlineSend: anIRSend ]
  189. ifFalse: [ super visitIRSend: anIRSend ]
  190. ! !
  191. IRJSTranslator subclass: #IRInliningJSTranslator
  192. instanceVariableNames: ''
  193. package: 'Compiler-Inlining'!
  194. !IRInliningJSTranslator commentStamp!
  195. I am a specialized JavaScript translator able to write inlined IR instructions to JavaScript stream (`JSStream` instance).!
  196. !IRInliningJSTranslator methodsFor: 'visiting'!
  197. visitIRInlinedAssignment: anIRInlinedAssignment
  198. self visit: anIRInlinedAssignment right
  199. !
  200. visitIRInlinedClosure: anIRInlinedClosure
  201. self stream nextPutVars: (anIRInlinedClosure tempDeclarations collect: [ :each |
  202. each name asVariableName ]).
  203. self visitAll: anIRInlinedClosure dagChildren
  204. !
  205. visitIRInlinedIfFalse: anIRInlinedIfFalse
  206. self stream nextPutIf: [
  207. self stream nextPutAll: '!!$core.assert('.
  208. self visit: anIRInlinedIfFalse dagChildren first.
  209. self stream nextPutAll: ')' ]
  210. then: [ self visit: anIRInlinedIfFalse dagChildren last ]
  211. !
  212. visitIRInlinedIfNilIfNotNil: anIRInlinedIfNilIfNotNil
  213. self stream
  214. nextPutIf: [
  215. | recvVarName |
  216. recvVarName := anIRInlinedIfNilIfNotNil receiverInternalVariableName.
  217. self stream nextPutAll: '(', recvVarName, ' = '.
  218. self visit: anIRInlinedIfNilIfNotNil dagChildren first.
  219. self stream nextPutAll: ') == null || ', recvVarName, '.isNil' ]
  220. then: [ self visit: anIRInlinedIfNilIfNotNil dagChildren second ]
  221. else: [ self visit: anIRInlinedIfNilIfNotNil dagChildren third ]
  222. !
  223. visitIRInlinedIfTrue: anIRInlinedIfTrue
  224. self stream nextPutIf: [
  225. self stream nextPutAll: '$core.assert('.
  226. self visit: anIRInlinedIfTrue dagChildren first.
  227. self stream nextPutAll: ')' ]
  228. then: [ self visit: anIRInlinedIfTrue dagChildren last ]
  229. !
  230. visitIRInlinedIfTrueIfFalse: anIRInlinedIfTrueIfFalse
  231. self stream
  232. nextPutIf: [
  233. self stream nextPutAll: '$core.assert('.
  234. self visit: anIRInlinedIfTrueIfFalse dagChildren first.
  235. self stream nextPutAll: ')' ]
  236. then: [ self visit: anIRInlinedIfTrueIfFalse dagChildren second ]
  237. else: [ self visit: anIRInlinedIfTrueIfFalse dagChildren third ]
  238. !
  239. visitIRInlinedNonLocalReturn: anIRInlinedReturn
  240. self stream nextPutStatementWith: [
  241. self visit: anIRInlinedReturn expression ].
  242. self stream nextPutNonLocalReturnWith: [ ]
  243. !
  244. visitIRInlinedReturn: anIRInlinedReturn
  245. self visit: anIRInlinedReturn expression
  246. !
  247. visitIRInlinedSequence: anIRInlinedSequence
  248. anIRInlinedSequence dagChildren do: [ :each |
  249. self stream nextPutStatementWith: [ self visit: each ]]
  250. ! !
  251. Object subclass: #IRSendInliner
  252. instanceVariableNames: 'send translator'
  253. package: 'Compiler-Inlining'!
  254. !IRSendInliner commentStamp!
  255. I inline some message sends and block closure arguments. I heavily rely on #perform: to dispatch inlining methods.!
  256. !IRSendInliner methodsFor: 'accessing'!
  257. send
  258. ^ send
  259. !
  260. send: anIRSend
  261. send := anIRSend
  262. !
  263. translator
  264. ^ translator
  265. !
  266. translator: anASTTranslator
  267. translator := anASTTranslator
  268. ! !
  269. !IRSendInliner methodsFor: 'error handling'!
  270. inliningError: aString
  271. InliningError signal: aString
  272. ! !
  273. !IRSendInliner methodsFor: 'factory'!
  274. inlinedClosure
  275. ^ IRInlinedClosure new
  276. !
  277. inlinedSequence
  278. ^ IRInlinedSequence new
  279. ! !
  280. !IRSendInliner methodsFor: 'inlining'!
  281. ifFalse: anIRInstruction
  282. ^ self inlinedSend: IRInlinedIfFalse new withBlock: anIRInstruction
  283. !
  284. ifFalse: anIRInstruction ifTrue: anotherIRInstruction
  285. ^ self perform: #ifTrue:ifFalse: withArguments: { anotherIRInstruction. anIRInstruction }
  286. !
  287. ifNil: anIRInstruction
  288. ^ self
  289. inlinedSend: IRInlinedIfNilIfNotNil new
  290. withBlock: anIRInstruction
  291. withBlock: (IRClosure new
  292. scope: anIRInstruction scope copy;
  293. add: (IRBlockSequence new
  294. add: self send receiver;
  295. yourself);
  296. yourself)
  297. !
  298. ifNil: anIRInstruction ifNotNil: anotherIRInstruction
  299. ^ self inlinedSend: IRInlinedIfNilIfNotNil new withBlock: anIRInstruction withBlock: anotherIRInstruction
  300. !
  301. ifNotNil: anIRInstruction
  302. ^ self
  303. inlinedSend: IRInlinedIfNilIfNotNil new
  304. withBlock: (IRClosure new
  305. scope: anIRInstruction scope copy;
  306. add: (IRBlockSequence new
  307. add: self send receiver;
  308. yourself);
  309. yourself)
  310. withBlock: anIRInstruction
  311. !
  312. ifNotNil: anIRInstruction ifNil: anotherIRInstruction
  313. ^ self inlinedSend: IRInlinedIfNilIfNotNil new withBlock: anotherIRInstruction withBlock: anIRInstruction
  314. !
  315. ifTrue: anIRInstruction
  316. ^ self inlinedSend: IRInlinedIfTrue new withBlock: anIRInstruction
  317. !
  318. ifTrue: anIRInstruction ifFalse: anotherIRInstruction
  319. ^ self inlinedSend: IRInlinedIfTrueIfFalse new withBlock: anIRInstruction withBlock: anotherIRInstruction
  320. !
  321. inlineClosure: anIRClosure
  322. | inlinedClosure sequence statements |
  323. inlinedClosure := self inlinedClosure.
  324. inlinedClosure
  325. scope: anIRClosure scope;
  326. parent: anIRClosure parent.
  327. "Add the possible temp declarations"
  328. anIRClosure tempDeclarations do: [ :each |
  329. inlinedClosure add: each ].
  330. "Add a block sequence"
  331. sequence := self inlinedSequence.
  332. "Map the closure arguments to the receiver of the message send"
  333. anIRClosure arguments do: [ :each |
  334. inlinedClosure add: (IRTempDeclaration new name: each; yourself).
  335. sequence add: (IRAssignment new
  336. add: (IRVariable new variable: (AliasVar new scope: inlinedClosure scope; name: each; yourself));
  337. add: (IRVariable new variable: (AliasVar new scope: inlinedClosure scope; name: '$receiver'; yourself));
  338. yourself) ].
  339. "To ensure the correct order of the closure instructions: first the temps then the sequence"
  340. inlinedClosure add: sequence.
  341. "Get all the statements"
  342. statements := anIRClosure sequence dagChildren.
  343. statements ifNotEmpty: [
  344. statements allButLast do: [ :each | sequence add: each ].
  345. "Inlined closures don't have implicit local returns"
  346. (statements last isReturn and: [ statements last isBlockReturn ])
  347. ifTrue: [ sequence add: statements last expression ]
  348. ifFalse: [ sequence add: statements last ] ].
  349. ^ inlinedClosure
  350. !
  351. inlineSend: anIRSend
  352. self send: anIRSend.
  353. ^ self
  354. perform: self send selector
  355. withArguments: self send arguments
  356. !
  357. inlinedSend: inlinedSend withBlock: anIRInstruction
  358. | inlinedClosure |
  359. anIRInstruction isClosure ifFalse: [ self inliningError: 'Message argument should be a block' ].
  360. anIRInstruction arguments size = 0 ifFalse: [ self inliningError: 'Inlined block should have zero argument' ].
  361. inlinedClosure := self translator visit: (self inlineClosure: anIRInstruction).
  362. inlinedSend
  363. add: self send receiver;
  364. add: inlinedClosure.
  365. self send replaceWith: inlinedSend.
  366. inlinedSend method internalVariables
  367. addAll: inlinedSend internalVariables.
  368. ^ inlinedSend
  369. !
  370. inlinedSend: inlinedSend withBlock: anIRInstruction withBlock: anotherIRInstruction
  371. | inlinedClosure1 inlinedClosure2 |
  372. anIRInstruction isClosure ifFalse: [ self inliningError: 'Message argument should be a block' ].
  373. anotherIRInstruction isClosure ifFalse: [ self inliningError: 'Message argument should be a block' ].
  374. inlinedClosure1 := self translator visit: (self inlineClosure: anIRInstruction).
  375. inlinedClosure2 := self translator visit: (self inlineClosure: anotherIRInstruction).
  376. inlinedSend
  377. add: self send receiver;
  378. add: inlinedClosure1;
  379. add: inlinedClosure2.
  380. self send replaceWith: inlinedSend.
  381. inlinedSend method internalVariables
  382. addAll: inlinedSend internalVariables.
  383. ^ inlinedSend
  384. ! !
  385. !IRSendInliner class methodsFor: 'accessing'!
  386. inlinedSelectors
  387. ^ #('ifTrue:' 'ifFalse:' 'ifTrue:ifFalse:' 'ifFalse:ifTrue:' 'ifNil:' 'ifNotNil:' 'ifNil:ifNotNil:' 'ifNotNil:ifNil:')
  388. !
  389. shouldInline: anIRSend
  390. (self inlinedSelectors includes: anIRSend selector) ifFalse: [ ^ false ].
  391. ^ anIRSend arguments allSatisfy: [ :each | each isClosure ]
  392. ! !
  393. IRSendInliner subclass: #IRAssignmentInliner
  394. instanceVariableNames: 'assignment'
  395. package: 'Compiler-Inlining'!
  396. !IRAssignmentInliner commentStamp!
  397. I inline message sends together with assignments by moving them around into the inline closure instructions.
  398. ##Example
  399. foo
  400. | a |
  401. a := true ifTrue: [ 1 ]
  402. Will produce:
  403. if($core.assert(true) {
  404. a = 1;
  405. };!
  406. !IRAssignmentInliner methodsFor: 'accessing'!
  407. assignment
  408. ^ assignment
  409. !
  410. assignment: aNode
  411. assignment := aNode
  412. ! !
  413. !IRAssignmentInliner methodsFor: 'inlining'!
  414. inlineAssignment: anIRAssignment
  415. | inlinedAssignment |
  416. self assignment: anIRAssignment.
  417. inlinedAssignment := IRInlinedAssignment new.
  418. anIRAssignment dagChildren do: [ :each |
  419. inlinedAssignment add: each ].
  420. anIRAssignment replaceWith: inlinedAssignment.
  421. self inlineSend: inlinedAssignment right.
  422. ^ inlinedAssignment
  423. !
  424. inlineClosure: anIRClosure
  425. | inlinedClosure statements |
  426. inlinedClosure := super inlineClosure: anIRClosure.
  427. statements := inlinedClosure sequence dagChildren.
  428. statements ifNotEmpty: [
  429. statements last canBeAssigned ifTrue: [
  430. statements last replaceWith: (IRAssignment new
  431. add: self assignment left;
  432. add: statements last copy;
  433. yourself) ] ].
  434. ^ inlinedClosure
  435. ! !
  436. IRSendInliner subclass: #IRReturnInliner
  437. instanceVariableNames: ''
  438. package: 'Compiler-Inlining'!
  439. !IRReturnInliner commentStamp!
  440. I inline message sends with inlined closure together with a return instruction.!
  441. !IRReturnInliner methodsFor: 'factory'!
  442. inlinedReturn
  443. ^ IRInlinedReturn new
  444. ! !
  445. !IRReturnInliner methodsFor: 'inlining'!
  446. inlineClosure: anIRClosure
  447. | closure statements |
  448. closure := super inlineClosure: anIRClosure.
  449. statements := closure sequence dagChildren.
  450. statements ifNotEmpty: [
  451. statements last isReturn
  452. ifFalse: [ statements last replaceWith: (IRReturn new
  453. add: statements last copy;
  454. yourself)] ].
  455. ^ closure
  456. !
  457. inlineReturn: anIRReturn
  458. | return |
  459. return := self inlinedReturn.
  460. anIRReturn dagChildren do: [ :each |
  461. return add: each ].
  462. anIRReturn replaceWith: return.
  463. self inlineSend: return expression.
  464. ^ return
  465. ! !
  466. CodeGenerator subclass: #InliningCodeGenerator
  467. instanceVariableNames: ''
  468. package: 'Compiler-Inlining'!
  469. !InliningCodeGenerator commentStamp!
  470. I am a specialized code generator that uses inlining to produce more optimized JavaScript output!
  471. !InliningCodeGenerator methodsFor: 'compiling'!
  472. compileNode: aNode
  473. | ir stream |
  474. self semanticAnalyzer visit: aNode.
  475. ir := self translator visit: aNode.
  476. self inliner visit: ir.
  477. ^ self irTranslator
  478. currentClass: self currentClass;
  479. visit: ir;
  480. contents
  481. !
  482. inliner
  483. ^ IRInliner new
  484. !
  485. irTranslator
  486. ^ IRInliningJSTranslator new
  487. ! !
  488. SemanticError subclass: #InliningError
  489. instanceVariableNames: ''
  490. package: 'Compiler-Inlining'!
  491. !InliningError commentStamp!
  492. Instances of InliningError are signaled when using an `InliningCodeGenerator`in a `Compiler`.!