Compiler-Inlining.st 15 KB

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