Platform-ImportExport.st 27 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140
  1. Smalltalk createPackage: 'Platform-ImportExport'!
  2. Object subclass: #AbstractExporter
  3. instanceVariableNames: ''
  4. package: 'Platform-ImportExport'!
  5. !AbstractExporter commentStamp!
  6. I am an abstract exporter for Amber source code.
  7. ## API
  8. Use `#exportPackage:on:` to export a given package on a Stream.!
  9. !AbstractExporter methodsFor: 'accessing'!
  10. extensionMethodsOfPackage: aPackage
  11. | result |
  12. result := OrderedCollection new.
  13. (self extensionProtocolsOfPackage: aPackage) do: [ :each |
  14. result addAll: each methods ].
  15. ^ result
  16. !
  17. extensionProtocolsOfPackage: aPackage
  18. | extensionName result |
  19. extensionName := '*', aPackage name.
  20. result := OrderedCollection new.
  21. "The classes must be loaded since it is extensions only.
  22. Therefore topological sorting (dependency resolution) does not matter here.
  23. Not sorting topologically improves the speed by a number of magnitude.
  24. Not to shuffle diffs, classes are sorted by their name."
  25. (Smalltalk classes asArray sorted: [ :a :b | a name < b name ]) do: [ :each |
  26. {each. each class} do: [ :behavior |
  27. (behavior protocols includes: extensionName) ifTrue: [
  28. result add: (ExportMethodProtocol name: extensionName theClass: behavior) ] ] ].
  29. ^ result
  30. ! !
  31. !AbstractExporter methodsFor: 'convenience'!
  32. classNameFor: aClass
  33. ^ aClass isMetaclass
  34. ifTrue: [ aClass instanceClass name, ' class' ]
  35. ifFalse: [
  36. aClass
  37. ifNil: [ 'nil' ]
  38. ifNotNil: [ aClass name ] ]
  39. ! !
  40. !AbstractExporter methodsFor: 'output'!
  41. exportPackage: aPackage on: aStream
  42. self subclassResponsibility
  43. ! !
  44. AbstractExporter subclass: #ChunkExporter
  45. instanceVariableNames: ''
  46. package: 'Platform-ImportExport'!
  47. !ChunkExporter commentStamp!
  48. I am an exporter dedicated to outputting Amber source code in the classic Smalltalk chunk format.
  49. I do not output any compiled code.!
  50. !ChunkExporter methodsFor: 'accessing'!
  51. extensionCategoriesOfPackage: aPackage
  52. "Issue #143: sort protocol alphabetically"
  53. | name map result |
  54. name := aPackage name.
  55. result := OrderedCollection new.
  56. (Package sortedClasses: Smalltalk classes) do: [ :each |
  57. {each. each class} do: [ :aClass |
  58. map := Dictionary new.
  59. aClass protocolsDo: [ :category :methods |
  60. category = ('*', name) ifTrue: [ map at: category put: methods ] ].
  61. result addAll: ((map keys sorted: [ :a :b | a <= b ]) collect: [ :category |
  62. MethodCategory name: category theClass: aClass methods: (map at: category) ]) ] ].
  63. ^ result
  64. !
  65. ownCategoriesOfClass: aClass
  66. "Answer the protocols of aClass that are not package extensions"
  67. "Issue #143: sort protocol alphabetically"
  68. | map |
  69. map := Dictionary new.
  70. aClass protocolsDo: [ :each :methods |
  71. (each match: '^\*') ifFalse: [ map at: each put: methods ] ].
  72. ^ (map keys sorted: [ :a :b | a <= b ]) collect: [ :each |
  73. MethodCategory name: each theClass: aClass methods: (map at: each) ]
  74. !
  75. ownCategoriesOfMetaClass: aClass
  76. "Issue #143: sort protocol alphabetically"
  77. ^ self ownCategoriesOfClass: aClass class
  78. !
  79. ownMethodProtocolsOfClass: aClass
  80. "Answer a collection of ExportMethodProtocol object of aClass that are not package extensions"
  81. ^ aClass ownProtocols collect: [ :each |
  82. ExportMethodProtocol name: each theClass: aClass ]
  83. ! !
  84. !ChunkExporter methodsFor: 'convenience'!
  85. chunkEscape: aString
  86. "Replace all occurrences of !! with !!!! and trim at both ends."
  87. ^ (aString replace: '!!' with: '!!!!') trimBoth
  88. ! !
  89. !ChunkExporter methodsFor: 'output'!
  90. exportCategoryEpilogueOf: aCategory on: aStream
  91. aStream nextPutAll: ' !!'; lf; lf
  92. !
  93. exportCategoryPrologueOf: aCategory on: aStream
  94. aStream
  95. nextPutAll: '!!', (self classNameFor: aCategory theClass);
  96. nextPutAll: ' methodsFor: ''', aCategory name, '''!!'
  97. !
  98. exportDefinitionOf: aClass on: aStream
  99. "Chunk format."
  100. aStream
  101. nextPutAll: (self classNameFor: aClass superclass);
  102. nextPutAll: ' subclass: #', (self classNameFor: aClass); lf;
  103. tab; nextPutAll: 'instanceVariableNames: '''.
  104. aClass instanceVariableNames
  105. do: [ :each | aStream nextPutAll: each ]
  106. separatedBy: [ aStream nextPutAll: ' ' ].
  107. aStream
  108. nextPutAll: ''''; lf;
  109. tab; nextPutAll: 'package: ''', aClass category, '''!!'; lf.
  110. aClass comment ifNotEmpty: [
  111. aStream
  112. nextPutAll: '!!', (self classNameFor: aClass), ' commentStamp!!';lf;
  113. nextPutAll: (self chunkEscape: aClass comment), '!!';lf ].
  114. aStream lf
  115. !
  116. exportMetaDefinitionOf: aClass on: aStream
  117. aClass class instanceVariableNames ifNotEmpty: [ :classIvars |
  118. aStream
  119. nextPutAll: (self classNameFor: aClass class);
  120. nextPutAll: ' instanceVariableNames: '''.
  121. classIvars
  122. do: [ :each | aStream nextPutAll: each ]
  123. separatedBy: [ aStream nextPutAll: ' ' ].
  124. aStream
  125. nextPutAll: '''!!'; lf; lf ]
  126. !
  127. exportMethod: aMethod on: aStream
  128. aStream
  129. lf; lf; nextPutAll: (self chunkEscape: aMethod source); lf;
  130. nextPutAll: '!!'
  131. !
  132. exportPackage: aPackage on: aStream
  133. self
  134. exportPackageDefinitionOf: aPackage on: aStream;
  135. exportPackageImportsOf: aPackage on: aStream.
  136. aPackage sortedClasses do: [ :each |
  137. each exportBehaviorDefinitionTo: aStream using: self.
  138. self
  139. exportProtocols: (self ownMethodProtocolsOfClass: each)
  140. on: aStream.
  141. each class isMetaclass ifTrue: [
  142. each class exportBehaviorDefinitionTo: aStream using: self.
  143. self
  144. exportProtocols: (self ownMethodProtocolsOfClass: each class)
  145. on: aStream ] ].
  146. self
  147. exportProtocols: (self extensionProtocolsOfPackage: aPackage)
  148. on: aStream
  149. !
  150. exportPackageDefinitionOf: aPackage on: aStream
  151. aStream
  152. nextPutAll: 'Smalltalk createPackage: ''', aPackage name, '''!!';
  153. lf
  154. !
  155. exportPackageImportsOf: aPackage on: aStream
  156. aPackage imports ifNotEmpty: [ :imports |
  157. aStream
  158. nextPutAll: '(Smalltalk packageAt: ''';
  159. nextPutAll: aPackage name;
  160. nextPutAll: ''') imports: ';
  161. nextPutAll: (self chunkEscape: aPackage importsDefinition);
  162. nextPutAll: '!!';
  163. lf ]
  164. !
  165. exportProtocol: aProtocol on: aStream
  166. self exportProtocolPrologueOf: aProtocol on: aStream.
  167. aProtocol methods do: [ :method |
  168. self exportMethod: method on: aStream ].
  169. self exportProtocolEpilogueOf: aProtocol on: aStream
  170. !
  171. exportProtocolEpilogueOf: aProtocol on: aStream
  172. aStream nextPutAll: ' !!'; lf; lf
  173. !
  174. exportProtocolPrologueOf: aProtocol on: aStream
  175. aStream
  176. nextPutAll: '!!', (self classNameFor: aProtocol theClass);
  177. nextPutAll: ' methodsFor: ''', aProtocol name, '''!!'
  178. !
  179. exportProtocols: aCollection on: aStream
  180. aCollection do: [ :each |
  181. self exportProtocol: each on: aStream ]
  182. ! !
  183. AbstractExporter subclass: #Exporter
  184. instanceVariableNames: ''
  185. package: 'Platform-ImportExport'!
  186. !Exporter commentStamp!
  187. I am responsible for outputting Amber code into a JavaScript string.
  188. The generated output is enough to reconstruct the exported data, including Smalltalk source code and other metadata.
  189. ## Use case
  190. I am typically used to save code outside of the Amber runtime (committing to disk, etc.).!
  191. !Exporter methodsFor: 'accessing'!
  192. ownMethodsOfClass: aClass
  193. "Issue #143: sort methods alphabetically"
  194. ^ ((aClass methodDictionary values) sorted: [ :a :b | a selector <= b selector ])
  195. reject: [ :each | (each protocol match: '^\*') ]
  196. !
  197. ownMethodsOfMetaClass: aClass
  198. "Issue #143: sort methods alphabetically"
  199. ^ self ownMethodsOfClass: aClass class
  200. ! !
  201. !Exporter methodsFor: 'convenience'!
  202. jsClassNameFor: aClass
  203. ^ aClass isMetaclass
  204. ifTrue: [ (self jsClassNameFor: aClass instanceClass), '.klass' ]
  205. ifFalse: [
  206. aClass
  207. ifNil: [ 'null' ]
  208. ifNotNil: [ '$globals.', aClass name ] ]
  209. ! !
  210. !Exporter methodsFor: 'output'!
  211. exportDefinitionOf: aClass on: aStream
  212. aStream
  213. lf;
  214. nextPutAll: '$core.addClass(';
  215. nextPutAll: '''', (self classNameFor: aClass), ''', ';
  216. nextPutAll: (self jsClassNameFor: aClass superclass);
  217. nextPutAll: ', ['.
  218. aClass instanceVariableNames
  219. do: [ :each | aStream nextPutAll: '''', each, '''' ]
  220. separatedBy: [ aStream nextPutAll: ', ' ].
  221. aStream
  222. nextPutAll: '], ''';
  223. nextPutAll: aClass category, '''';
  224. nextPutAll: ');'.
  225. aClass comment ifNotEmpty: [
  226. aStream
  227. lf;
  228. nextPutAll: '//>>excludeStart("ide", pragmas.excludeIdeData);';
  229. lf;
  230. nextPutAll: (self jsClassNameFor: aClass);
  231. nextPutAll: '.comment=';
  232. nextPutAll: aClass comment crlfSanitized asJavascript;
  233. nextPutAll: ';';
  234. lf;
  235. nextPutAll: '//>>excludeEnd("ide");' ].
  236. aStream lf
  237. !
  238. exportMetaDefinitionOf: aClass on: aStream
  239. aStream lf.
  240. aClass class instanceVariableNames ifNotEmpty: [ :classIvars |
  241. aStream
  242. nextPutAll: (self jsClassNameFor: aClass class);
  243. nextPutAll: '.iVarNames = ['.
  244. classIvars
  245. do: [ :each | aStream nextPutAll: '''', each, '''' ]
  246. separatedBy: [ aStream nextPutAll: ',' ].
  247. aStream nextPutAll: '];', String lf ]
  248. !
  249. exportMethod: aMethod on: aStream
  250. aStream
  251. nextPutAll: '$core.addMethod(';lf;
  252. nextPutAll: '$core.method({';lf;
  253. nextPutAll: 'selector: ', aMethod selector asJavascript, ',';lf;
  254. nextPutAll: 'protocol: ''', aMethod protocol, ''',';lf;
  255. nextPutAll: 'fn: ', aMethod fn compiledSource, ',';lf;
  256. nextPutAll: '//>>excludeStart("ide", pragmas.excludeIdeData);';lf;
  257. nextPutAll: 'args: ', aMethod arguments asJavascript, ','; lf;
  258. nextPutAll: 'source: ', aMethod source asJavascript, ',';lf;
  259. nextPutAll: 'referencedClasses: ', aMethod referencedClasses asJavascript, ',';lf;
  260. nextPutAll: '//>>excludeEnd("ide");';lf;
  261. nextPutAll: 'messageSends: ', aMethod messageSends asJavascript;lf;
  262. nextPutAll: '}),';lf;
  263. nextPutAll: (self jsClassNameFor: aMethod methodClass);
  264. nextPutAll: ');';lf;lf
  265. !
  266. exportPackage: aPackage on: aStream
  267. self
  268. exportPackagePrologueOf: aPackage on: aStream;
  269. exportPackageDefinitionOf: aPackage on: aStream;
  270. exportPackageContextOf: aPackage on: aStream;
  271. exportPackageImportsOf: aPackage on: aStream;
  272. exportPackageTransportOf: aPackage on: aStream.
  273. aPackage sortedClasses do: [ :each |
  274. each exportBehaviorDefinitionTo: aStream using: self.
  275. each ownMethods do: [ :method |
  276. self exportMethod: method on: aStream ].
  277. each class isMetaclass ifTrue: [
  278. each class exportBehaviorDefinitionTo: aStream using: self.
  279. each class ownMethods do: [ :method |
  280. self exportMethod: method on: aStream ] ] ].
  281. (self extensionMethodsOfPackage: aPackage) do: [ :each |
  282. self exportMethod: each on: aStream ].
  283. self exportPackageEpilogueOf: aPackage on: aStream
  284. !
  285. exportPackageBodyBlockPrologueOf: aPackage on: aStream
  286. aStream
  287. nextPutAll: 'if(!!$boot.nilAsReceiver)$boot.nilAsReceiver=$boot.nil;';
  288. lf;
  289. nextPutAll: 'var $core=$boot.api,nil=$boot.nilAsReceiver,$recv=$boot.asReceiver,$globals=$boot.globals;';
  290. lf;
  291. nextPutAll: 'if(!!$boot.nilAsClass)$boot.nilAsClass=$boot.dnu;';
  292. lf
  293. !
  294. exportPackageContextOf: aPackage on: aStream
  295. aStream
  296. nextPutAll: '$core.packages[';
  297. nextPutAll: aPackage name asJavascript;
  298. nextPutAll: '].innerEval = ';
  299. nextPutAll: 'function (expr) { return eval(expr); }';
  300. nextPutAll: ';';
  301. lf
  302. !
  303. exportPackageDefinitionOf: aPackage on: aStream
  304. aStream
  305. nextPutAll: '$core.addPackage(';
  306. nextPutAll: '''', aPackage name, ''');';
  307. lf
  308. !
  309. exportPackageEpilogueOf: aPackage on: aStream
  310. self subclassResponsibility
  311. !
  312. exportPackageImportsOf: aPackage on: aStream
  313. aPackage importsAsJson ifNotEmpty: [ :imports |
  314. aStream
  315. nextPutAll: '$core.packages[';
  316. nextPutAll: aPackage name asJavascript;
  317. nextPutAll: '].imports = ';
  318. nextPutAll: imports asJavascript;
  319. nextPutAll: ';';
  320. lf ]
  321. !
  322. exportPackagePrologueOf: aPackage on: aStream
  323. self subclassResponsibility
  324. !
  325. exportPackageTransportOf: aPackage on: aStream
  326. aStream
  327. nextPutAll: '$core.packages[';
  328. nextPutAll: aPackage name asJavascript;
  329. nextPutAll: '].transport = ';
  330. nextPutAll: aPackage transport asJSONString;
  331. nextPutAll: ';';
  332. lf
  333. ! !
  334. Exporter subclass: #AmdExporter
  335. instanceVariableNames: 'namespace'
  336. package: 'Platform-ImportExport'!
  337. !AmdExporter commentStamp!
  338. I am used to export Packages in an AMD (Asynchronous Module Definition) JavaScript format.!
  339. !AmdExporter methodsFor: 'output'!
  340. exportPackageEpilogueOf: aPackage on: aStream
  341. aStream
  342. nextPutAll: '});';
  343. lf
  344. !
  345. exportPackagePrologueOf: aPackage on: aStream
  346. | importsForOutput loadDependencies pragmaStart pragmaEnd |
  347. pragmaStart := ''.
  348. pragmaEnd := ''.
  349. importsForOutput := self importsForOutput: aPackage.
  350. loadDependencies := self amdNamesOfPackages: aPackage loadDependencies.
  351. importsForOutput value ifNotEmpty: [
  352. pragmaStart := String lf, '//>>excludeStart("imports", pragmas.excludeImports);', String lf.
  353. pragmaEnd := String lf, '//>>excludeEnd("imports");', String lf ].
  354. aStream
  355. nextPutAll: 'define(';
  356. nextPutAll: (((
  357. (#('amber/boot' ':1:'), importsForOutput value, #(':2:'), loadDependencies asArray sorted) asJavascript)
  358. replace: ',\s*["'']:1:["'']' with: pragmaStart) replace: ',\s*["'']:2:["'']' with: pragmaEnd);
  359. nextPutAll: ', function(';
  360. nextPutAll: (((
  361. (#('$boot' ':1:'), importsForOutput key, #(':2:')) join: ',')
  362. replace: ',\s*:1:' with: pragmaStart) replace: ',\s*:2:' with: pragmaEnd);
  363. nextPutAll: '){"use strict";';
  364. lf.
  365. self exportPackageBodyBlockPrologueOf: aPackage on: aStream
  366. ! !
  367. !AmdExporter methodsFor: 'private'!
  368. amdNamesOfPackages: anArray
  369. ^ (anArray
  370. select: [ :each | (self amdNamespaceOfPackage: each) notNil ])
  371. collect: [ :each | (self amdNamespaceOfPackage: each), '/', each name ]
  372. !
  373. amdNamespaceOfPackage: aPackage
  374. ^ (aPackage transport type = 'amd')
  375. ifTrue: [ aPackage transport namespace ]
  376. ifFalse: [ nil ]
  377. !
  378. importsForOutput: aPackage
  379. "Returns an association where key is list of import variables
  380. and value is list of external dependencies, with ones imported as variables
  381. put at the beginning with same order as is in key.
  382. For example imports:{'jQuery'->'jquery'. 'bootstrap'} would yield
  383. #('jQuery') -> #('jquery' 'bootstrap')"
  384. | namedImports anonImports importVarNames |
  385. namedImports := #().
  386. anonImports := #().
  387. importVarNames := #().
  388. aPackage imports do: [ :each | each isString
  389. ifTrue: [ anonImports add: each ]
  390. ifFalse: [ namedImports add: each value.
  391. importVarNames add: each key ]].
  392. ^ importVarNames -> (namedImports, anonImports)
  393. ! !
  394. Object subclass: #ChunkParser
  395. instanceVariableNames: 'stream last'
  396. package: 'Platform-ImportExport'!
  397. !ChunkParser commentStamp!
  398. I am responsible for parsing aStream contents in the chunk format.
  399. ## API
  400. ChunkParser new
  401. stream: aStream;
  402. nextChunk!
  403. !ChunkParser methodsFor: 'accessing'!
  404. last
  405. ^ last
  406. !
  407. stream: aStream
  408. stream := aStream
  409. ! !
  410. !ChunkParser methodsFor: 'reading'!
  411. nextChunk
  412. "The chunk format (Smalltalk Interchange Format or Fileout format)
  413. is a trivial format but can be a bit tricky to understand:
  414. - Uses the exclamation mark as delimiter of chunks.
  415. - Inside a chunk a normal exclamation mark must be doubled.
  416. - A non empty chunk must be a valid Smalltalk expression.
  417. - A chunk on top level with a preceding empty chunk is an instruction chunk:
  418. - The object created by the expression then takes over reading chunks.
  419. This method returns next chunk as a String (trimmed), empty String (all whitespace) or nil."
  420. | char result chunk |
  421. result := '' writeStream.
  422. [ char := stream next.
  423. char notNil ] whileTrue: [
  424. char = '!!' ifTrue: [
  425. stream peek = '!!'
  426. ifTrue: [ stream next "skipping the escape double" ]
  427. ifFalse: [ ^ last := result contents trimBoth "chunk end marker found" ]].
  428. result nextPut: char ].
  429. ^ last := nil "a chunk needs to end with !!"
  430. ! !
  431. !ChunkParser class methodsFor: 'instance creation'!
  432. on: aStream
  433. ^ self new stream: aStream
  434. ! !
  435. Object subclass: #ClassCommentReader
  436. instanceVariableNames: 'class'
  437. package: 'Platform-ImportExport'!
  438. !ClassCommentReader commentStamp!
  439. I provide a mechanism for retrieving class comments stored on a file.
  440. See also `ClassCategoryReader`.!
  441. !ClassCommentReader methodsFor: 'accessing'!
  442. class: aClass
  443. class := aClass
  444. ! !
  445. !ClassCommentReader methodsFor: 'fileIn'!
  446. scanFrom: aChunkParser
  447. | chunk |
  448. chunk := aChunkParser nextChunk.
  449. chunk ifNotEmpty: [
  450. self setComment: chunk ].
  451. ! !
  452. !ClassCommentReader methodsFor: 'initialization'!
  453. initialize
  454. super initialize.
  455. ! !
  456. !ClassCommentReader methodsFor: 'private'!
  457. setComment: aString
  458. class comment: aString
  459. ! !
  460. Object subclass: #ClassProtocolReader
  461. instanceVariableNames: 'class category'
  462. package: 'Platform-ImportExport'!
  463. !ClassProtocolReader commentStamp!
  464. I provide a mechanism for retrieving class descriptions stored on a file in the Smalltalk chunk format.!
  465. !ClassProtocolReader methodsFor: 'accessing'!
  466. class: aClass category: aString
  467. class := aClass.
  468. category := aString
  469. ! !
  470. !ClassProtocolReader methodsFor: 'fileIn'!
  471. scanFrom: aChunkParser
  472. | chunk |
  473. [ chunk := aChunkParser nextChunk.
  474. chunk isEmpty ] whileFalse: [
  475. self compileMethod: chunk ]
  476. ! !
  477. !ClassProtocolReader methodsFor: 'initialization'!
  478. initialize
  479. super initialize.
  480. ! !
  481. !ClassProtocolReader methodsFor: 'private'!
  482. compileMethod: aString
  483. Compiler new install: aString forClass: class protocol: category
  484. ! !
  485. Object subclass: #ExportMethodProtocol
  486. instanceVariableNames: 'name theClass'
  487. package: 'Platform-ImportExport'!
  488. !ExportMethodProtocol commentStamp!
  489. I am an abstraction for a method protocol in a class / metaclass.
  490. I know of my class, name and methods.
  491. I am used when exporting a package.!
  492. !ExportMethodProtocol methodsFor: 'accessing'!
  493. methods
  494. ^ (self theClass methodsInProtocol: self name)
  495. sorted: [ :a :b | a selector <= b selector ]
  496. !
  497. name
  498. ^ name
  499. !
  500. name: aString
  501. name := aString
  502. !
  503. theClass
  504. ^ theClass
  505. !
  506. theClass: aClass
  507. theClass := aClass
  508. ! !
  509. !ExportMethodProtocol class methodsFor: 'instance creation'!
  510. name: aString theClass: aClass
  511. ^ self new
  512. name: aString;
  513. theClass: aClass;
  514. yourself
  515. ! !
  516. Object subclass: #Importer
  517. instanceVariableNames: 'lastSection lastChunk'
  518. package: 'Platform-ImportExport'!
  519. !Importer commentStamp!
  520. I can import Amber code from a string in the chunk format.
  521. ## API
  522. Importer new import: aString!
  523. !Importer methodsFor: 'accessing'!
  524. lastChunk
  525. ^ lastChunk
  526. !
  527. lastSection
  528. ^ lastSection
  529. ! !
  530. !Importer methodsFor: 'fileIn'!
  531. import: aStream
  532. | chunk result parser lastEmpty |
  533. parser := ChunkParser on: aStream.
  534. lastEmpty := false.
  535. lastSection := 'n/a, not started'.
  536. lastChunk := nil.
  537. [
  538. [ chunk := parser nextChunk.
  539. chunk isNil ] whileFalse: [
  540. chunk
  541. ifEmpty: [ lastEmpty := true ]
  542. ifNotEmpty: [
  543. lastSection := chunk.
  544. result := Compiler new evaluateExpression: chunk.
  545. lastEmpty
  546. ifTrue: [
  547. lastEmpty := false.
  548. result scanFrom: parser ]] ].
  549. lastSection := 'n/a, finished'
  550. ] on: Error do: [:e | lastChunk := parser last. e resignal ].
  551. ! !
  552. Error subclass: #PackageCommitError
  553. instanceVariableNames: ''
  554. package: 'Platform-ImportExport'!
  555. !PackageCommitError commentStamp!
  556. I get signaled when an attempt to commit a package has failed.!
  557. Object subclass: #PackageHandler
  558. instanceVariableNames: ''
  559. package: 'Platform-ImportExport'!
  560. !PackageHandler commentStamp!
  561. I am responsible for handling package loading and committing.
  562. I should not be used directly. Instead, use the corresponding `Package` methods.!
  563. !PackageHandler methodsFor: 'accessing'!
  564. chunkContentsFor: aPackage
  565. ^ String streamContents: [ :str |
  566. self chunkExporter exportPackage: aPackage on: str ]
  567. !
  568. chunkExporterClass
  569. ^ ChunkExporter
  570. !
  571. commitPathJsFor: aPackage
  572. self subclassResponsibility
  573. !
  574. commitPathStFor: aPackage
  575. self subclassResponsibility
  576. !
  577. contentsFor: aPackage
  578. ^ String streamContents: [ :str |
  579. self exporter exportPackage: aPackage on: str ]
  580. !
  581. exporterClass
  582. self subclassResponsibility
  583. ! !
  584. !PackageHandler methodsFor: 'committing'!
  585. commit: aPackage
  586. self
  587. commit: aPackage
  588. onSuccess: []
  589. onError: [ :error |
  590. PackageCommitError new
  591. messageText: 'Commiting failed with reason: "' , (error responseText) , '"';
  592. signal ]
  593. !
  594. commit: aPackage onSuccess: aBlock onError: anotherBlock
  595. self
  596. commitJsFileFor: aPackage
  597. onSuccess: [
  598. self
  599. commitStFileFor: aPackage
  600. onSuccess: [ aPackage beClean. aBlock value ]
  601. onError: anotherBlock ]
  602. onError: anotherBlock
  603. !
  604. commitJsFileFor: aPackage onSuccess: aBlock onError: anotherBlock
  605. self
  606. ajaxPutAt: (self commitPathJsFor: aPackage), '/', aPackage name, '.js'
  607. data: (self contentsFor: aPackage)
  608. onSuccess: aBlock
  609. onError: anotherBlock
  610. !
  611. commitStFileFor: aPackage onSuccess: aBlock onError: anotherBlock
  612. self
  613. ajaxPutAt: (self commitPathStFor: aPackage), '/', aPackage name, '.st'
  614. data: (self chunkContentsFor: aPackage)
  615. onSuccess: aBlock
  616. onError: anotherBlock
  617. ! !
  618. !PackageHandler methodsFor: 'error handling'!
  619. onCommitError: anError
  620. PackageCommitError new
  621. messageText: 'Commiting failed with reason: "' , (anError responseText) , '"';
  622. signal
  623. ! !
  624. !PackageHandler methodsFor: 'factory'!
  625. chunkExporter
  626. ^ self chunkExporterClass new
  627. !
  628. exporter
  629. ^ self exporterClass new
  630. ! !
  631. !PackageHandler methodsFor: 'loading'!
  632. load: aPackage
  633. self subclassResponsibility
  634. ! !
  635. !PackageHandler methodsFor: 'private'!
  636. ajaxPutAt: aURL data: aString onSuccess: aBlock onError: anotherBlock
  637. | xhr |
  638. xhr := Platform newXhr.
  639. xhr open: 'PUT' url: aURL async: true.
  640. xhr onreadystatechange: [
  641. xhr readyState = 4 ifTrue: [
  642. (xhr status >= 200 and: [ xhr status < 300 ])
  643. ifTrue: aBlock
  644. ifFalse: anotherBlock ]].
  645. xhr send: aString
  646. ! !
  647. PackageHandler subclass: #AmdPackageHandler
  648. instanceVariableNames: ''
  649. package: 'Platform-ImportExport'!
  650. !AmdPackageHandler commentStamp!
  651. I am responsible for handling package loading and committing.
  652. I should not be used directly. Instead, use the corresponding `Package` methods.!
  653. !AmdPackageHandler methodsFor: 'accessing'!
  654. commitPathJsFor: aPackage
  655. ^ self toUrl: (self namespaceFor: aPackage)
  656. !
  657. commitPathStFor: aPackage
  658. "If _source is not mapped, .st will be committed to .js path.
  659. It is recommended not to use _source as it can be deprecated."
  660. | path pathWithout |
  661. path := self toUrl: (self namespaceFor: aPackage), '/_source'.
  662. pathWithout := self commitPathJsFor: aPackage.
  663. ^ path = (pathWithout, '/_source') ifTrue: [ pathWithout ] ifFalse: [ path ]
  664. !
  665. exporterClass
  666. ^ AmdExporter
  667. ! !
  668. !AmdPackageHandler methodsFor: 'committing'!
  669. namespaceFor: aPackage
  670. ^ aPackage transport namespace
  671. ! !
  672. !AmdPackageHandler methodsFor: 'loading'!
  673. load: aPackage
  674. Smalltalk amdRequire
  675. ifNil: [ self error: 'AMD loader not present' ]
  676. ifNotNil: [ :require |
  677. require value: (Array with: (self namespaceFor: aPackage), '/', aPackage name ) ]
  678. ! !
  679. !AmdPackageHandler methodsFor: 'private'!
  680. toUrl: aString
  681. ^ Smalltalk amdRequire
  682. ifNil: [ self error: 'AMD loader not present' ]
  683. ifNotNil: [ :require | (require basicAt: 'toUrl') value: aString ]
  684. ! !
  685. !AmdPackageHandler class methodsFor: 'commit paths'!
  686. defaultNamespace
  687. ^ Smalltalk defaultAmdNamespace
  688. !
  689. defaultNamespace: aString
  690. Smalltalk defaultAmdNamespace: aString
  691. ! !
  692. Object subclass: #PackageTransport
  693. instanceVariableNames: 'package'
  694. package: 'Platform-ImportExport'!
  695. !PackageTransport commentStamp!
  696. I represent the transport mechanism used to commit a package.
  697. My concrete subclasses have a `#handler` to which committing is delegated.!
  698. !PackageTransport methodsFor: 'accessing'!
  699. commitHandlerClass
  700. self subclassResponsibility
  701. !
  702. definition
  703. ^ ''
  704. !
  705. package
  706. ^ package
  707. !
  708. package: aPackage
  709. package := aPackage
  710. !
  711. type
  712. ^ self class type
  713. ! !
  714. !PackageTransport methodsFor: 'committing'!
  715. commit
  716. self commitHandler commit: self package
  717. !
  718. commitOnSuccess: aBlock onError: anotherBlock
  719. self commitHandler
  720. commit: self package
  721. onSuccess: aBlock
  722. onError: anotherBlock
  723. ! !
  724. !PackageTransport methodsFor: 'converting'!
  725. asJSON
  726. ^ #{ 'type' -> self type }
  727. ! !
  728. !PackageTransport methodsFor: 'factory'!
  729. commitHandler
  730. ^ self commitHandlerClass new
  731. ! !
  732. !PackageTransport methodsFor: 'initialization'!
  733. setupFromJson: anObject
  734. "no op. override if needed in subclasses"
  735. ! !
  736. !PackageTransport methodsFor: 'loading'!
  737. load
  738. self commitHandler load: self package
  739. ! !
  740. PackageTransport class instanceVariableNames: 'registry'!
  741. !PackageTransport class methodsFor: 'accessing'!
  742. classRegisteredFor: aString
  743. ^ registry at: aString
  744. !
  745. defaultType
  746. ^ AmdPackageTransport type
  747. !
  748. type
  749. "Override in subclasses"
  750. ^ nil
  751. ! !
  752. !PackageTransport class methodsFor: 'initialization'!
  753. initialize
  754. super initialize.
  755. self == PackageTransport
  756. ifTrue: [ registry := #{} ]
  757. ifFalse: [ self register ]
  758. ! !
  759. !PackageTransport class methodsFor: 'instance creation'!
  760. for: aString
  761. ^ (self classRegisteredFor: aString) new
  762. !
  763. fromJson: anObject
  764. anObject ifNil: [ ^ self for: self defaultType ].
  765. ^ (self for: anObject type)
  766. setupFromJson: anObject;
  767. yourself
  768. ! !
  769. !PackageTransport class methodsFor: 'registration'!
  770. register
  771. PackageTransport register: self
  772. !
  773. register: aClass
  774. aClass type ifNotNil: [
  775. registry at: aClass type put: aClass ]
  776. ! !
  777. PackageTransport subclass: #AmdPackageTransport
  778. instanceVariableNames: 'namespace'
  779. package: 'Platform-ImportExport'!
  780. !AmdPackageTransport commentStamp!
  781. I am the default transport for committing packages.
  782. See `AmdExporter` and `AmdPackageHandler`.!
  783. !AmdPackageTransport methodsFor: 'accessing'!
  784. commitHandlerClass
  785. ^ AmdPackageHandler
  786. !
  787. definition
  788. ^ String streamContents: [ :stream |
  789. stream
  790. nextPutAll: self class name;
  791. nextPutAll: ' namespace: ';
  792. nextPutAll: '''', self namespace, '''' ]
  793. !
  794. namespace
  795. ^ namespace ifNil: [ self defaultNamespace ]
  796. !
  797. namespace: aString
  798. namespace := aString
  799. ! !
  800. !AmdPackageTransport methodsFor: 'actions'!
  801. setPath: aString
  802. "Set the path the the receiver's `namespace`"
  803. (require basicAt: 'config') value: #{
  804. 'paths' -> #{
  805. self namespace -> aString
  806. }
  807. }.
  808. ! !
  809. !AmdPackageTransport methodsFor: 'converting'!
  810. asJSON
  811. ^ super asJSON
  812. at: 'amdNamespace' put: self namespace;
  813. yourself
  814. ! !
  815. !AmdPackageTransport methodsFor: 'defaults'!
  816. defaultNamespace
  817. ^ Smalltalk defaultAmdNamespace
  818. ! !
  819. !AmdPackageTransport methodsFor: 'initialization'!
  820. setupFromJson: anObject
  821. self namespace: (anObject at: 'amdNamespace')
  822. ! !
  823. !AmdPackageTransport methodsFor: 'printing'!
  824. printOn: aStream
  825. super printOn: aStream.
  826. aStream
  827. nextPutAll: ' (AMD Namespace: ';
  828. nextPutAll: self namespace;
  829. nextPutAll: ')'
  830. ! !
  831. !AmdPackageTransport class methodsFor: 'accessing'!
  832. type
  833. ^ 'amd'
  834. ! !
  835. !AmdPackageTransport class methodsFor: 'instance creation'!
  836. namespace: aString
  837. ^ self new
  838. namespace: aString;
  839. yourself
  840. ! !
  841. !Behavior methodsFor: '*Platform-ImportExport'!
  842. commentStamp
  843. ^ ClassCommentReader new
  844. class: self;
  845. yourself
  846. !
  847. commentStamp: aStamp prior: prior
  848. ^ self commentStamp
  849. !
  850. exportBehaviorDefinitionTo: aStream using: anExporter
  851. self subclassResponsibility
  852. !
  853. methodsFor: aString
  854. ^ ClassProtocolReader new
  855. class: self category: aString;
  856. yourself
  857. !
  858. methodsFor: aString stamp: aStamp
  859. "Added for file-in compatibility, ignores stamp."
  860. ^ self methodsFor: aString
  861. ! !
  862. !Class methodsFor: '*Platform-ImportExport'!
  863. exportBehaviorDefinitionTo: aStream using: anExporter
  864. anExporter exportDefinitionOf: self on: aStream
  865. ! !
  866. !Metaclass methodsFor: '*Platform-ImportExport'!
  867. exportBehaviorDefinitionTo: aStream using: anExporter
  868. anExporter exportMetaDefinitionOf: self instanceClass on: aStream
  869. ! !
  870. !Package methodsFor: '*Platform-ImportExport'!
  871. commit
  872. ^ self transport commit
  873. !
  874. load
  875. ^ self transport load
  876. !
  877. loadFromNamespace: aString
  878. ^ self transport
  879. namespace: aString;
  880. load
  881. ! !
  882. !Package class methodsFor: '*Platform-ImportExport'!
  883. load: aPackageName
  884. (self named: aPackageName) load
  885. !
  886. load: aPackageName fromNamespace: aString
  887. (self named: aPackageName) loadFromNamespace: aString
  888. ! !