Importer-Exporter.st 22 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869
  1. Smalltalk current createPackage: 'Importer-Exporter'!
  2. Object subclass: #AmdExporter
  3. instanceVariableNames: ''
  4. package: 'Importer-Exporter'!
  5. !AmdExporter class methodsFor: 'exporting-output'!
  6. exportPackageEpilogueOf: aPackage on: aStream
  7. aStream
  8. nextPutAll: '});';
  9. lf
  10. !
  11. exportPackagePrologueOf: aPackage on: aStream
  12. aStream
  13. nextPutAll: 'define("';
  14. nextPutAll: (aPackage amdNamespace ifNil: [ 'amber' ]); "ifNil: only for LegacyPH, it should not happen with AmdPH"
  15. nextPutAll: '/';
  16. nextPutAll: aPackage name;
  17. nextPutAll: '", ';
  18. nextPutAll: (#('amber_vm/smalltalk' 'amber_vm/nil' 'amber_vm/_st'), (self amdNamesOfPackages: aPackage loadDependencies)) asJavascript;
  19. nextPutAll: ', function(smalltalk,nil,_st){';
  20. lf
  21. !
  22. exportPackageTransportOf: aPackage on: aStream
  23. aStream
  24. nextPutAll: 'smalltalk.packages[';
  25. nextPutAll: aPackage name asJavascript;
  26. nextPutAll: '].transport = ';
  27. nextPutAll: aPackage transportJson;
  28. nextPutAll: ';';
  29. lf
  30. ! !
  31. !AmdExporter class methodsFor: 'private'!
  32. amdNamesOfPackages: anArray
  33. | deps depNames |
  34. ^(anArray
  35. select: [ :each | each amdNamespace notNil ])
  36. collect: [ :each | each amdNamespace, '/', each name ]
  37. ! !
  38. Object subclass: #ChunkExporter
  39. instanceVariableNames: ''
  40. package: 'Importer-Exporter'!
  41. !ChunkExporter commentStamp!
  42. I am an exporter dedicated to outputting Amber source code in the classic Smalltalk chunk format.
  43. I do not output any compiled code.!
  44. !ChunkExporter class methodsFor: 'exporting-accessing'!
  45. extensionCategoriesOfPackage: package
  46. "Issue #143: sort protocol alphabetically"
  47. | name map result |
  48. name := package name.
  49. result := OrderedCollection new.
  50. (Package sortedClasses: Smalltalk current classes) do: [:each |
  51. {each. each class} do: [:aClass |
  52. map := Dictionary new.
  53. aClass protocolsDo: [:category :methods |
  54. (category match: '^\*', name) ifTrue: [ map at: category put: methods ]].
  55. result addAll: ((map keys sorted: [:a :b | a <= b ]) collect: [:category |
  56. MethodCategory name: category class: aClass methods: (map at: category)]) ]].
  57. ^result
  58. !
  59. methodsOfCategory: category
  60. "Issue #143: sort methods alphabetically"
  61. ^(category methods) sorted: [:a :b | a selector <= b selector]
  62. !
  63. ownCategoriesOfClass: aClass
  64. "Issue #143: sort protocol alphabetically"
  65. | map |
  66. map := Dictionary new.
  67. aClass protocolsDo: [:category :methods |
  68. (category match: '^\*') ifFalse: [ map at: category put: methods ]].
  69. ^(map keys sorted: [:a :b | a <= b ]) collect: [:category |
  70. MethodCategory name: category class: aClass methods: (map at: category) ]
  71. !
  72. ownCategoriesOfMetaClass: aClass
  73. "Issue #143: sort protocol alphabetically"
  74. ^self ownCategoriesOfClass: aClass class
  75. ! !
  76. !ChunkExporter class methodsFor: 'exporting-output'!
  77. exportCategoryEpilogueOf: category on: aStream
  78. aStream nextPutAll: ' !!'; lf; lf
  79. !
  80. exportCategoryPrologueOf: category on: aStream
  81. aStream
  82. nextPutAll: '!!', (self classNameFor: category klass);
  83. nextPutAll: ' methodsFor: ''', category name, '''!!'
  84. !
  85. exportDefinitionOf: aClass on: aStream
  86. "Chunk format."
  87. aStream
  88. nextPutAll: (self classNameFor: aClass superclass);
  89. nextPutAll: ' subclass: #', (self classNameFor: aClass); lf;
  90. tab; nextPutAll: 'instanceVariableNames: '''.
  91. aClass instanceVariableNames
  92. do: [:each | aStream nextPutAll: each]
  93. separatedBy: [aStream nextPutAll: ' '].
  94. aStream
  95. nextPutAll: ''''; lf;
  96. tab; nextPutAll: 'package: ''', aClass category, '''!!'; lf.
  97. aClass comment notEmpty ifTrue: [
  98. aStream
  99. nextPutAll: '!!', (self classNameFor: aClass), ' commentStamp!!';lf;
  100. nextPutAll: (self chunkEscape: aClass comment), '!!';lf].
  101. aStream lf
  102. !
  103. exportMetaDefinitionOf: aClass on: aStream
  104. aClass class instanceVariableNames isEmpty ifFalse: [
  105. aStream
  106. nextPutAll: (self classNameFor: aClass class);
  107. nextPutAll: ' instanceVariableNames: '''.
  108. aClass class instanceVariableNames
  109. do: [:each | aStream nextPutAll: each]
  110. separatedBy: [aStream nextPutAll: ' '].
  111. aStream
  112. nextPutAll: '''!!'; lf; lf]
  113. !
  114. exportMethod: aMethod on: aStream
  115. aStream
  116. lf; lf; nextPutAll: (self chunkEscape: aMethod source); lf;
  117. nextPutAll: '!!'
  118. !
  119. exportPackageDefinitionOf: package on: aStream
  120. "Chunk format."
  121. aStream
  122. nextPutAll: 'Smalltalk current createPackage: ''', package name, '''!!';
  123. lf
  124. ! !
  125. !ChunkExporter class methodsFor: 'fileOut'!
  126. recipe
  127. "Export a given package."
  128. | exportCategoryRecipe |
  129. exportCategoryRecipe := {
  130. self -> #exportCategoryPrologueOf:on:.
  131. {
  132. self -> #methodsOfCategory:.
  133. self -> #exportMethod:on: }.
  134. self -> #exportCategoryEpilogueOf:on: }.
  135. ^{
  136. self -> #exportPackageDefinitionOf:on:.
  137. {
  138. PluggableExporter -> #ownClassesOfPackage:.
  139. self -> #exportDefinitionOf:on:.
  140. { self -> #ownCategoriesOfClass: }, exportCategoryRecipe.
  141. self -> #exportMetaDefinitionOf:on:.
  142. { self -> #ownCategoriesOfMetaClass: }, exportCategoryRecipe }.
  143. { self -> #extensionCategoriesOfPackage: }, exportCategoryRecipe
  144. }
  145. ! !
  146. !ChunkExporter class methodsFor: 'private'!
  147. chunkEscape: aString
  148. "Replace all occurrences of !! with !!!! and trim at both ends."
  149. ^(aString replace: '!!' with: '!!!!') trimBoth
  150. !
  151. classNameFor: aClass
  152. ^aClass isMetaclass
  153. ifTrue: [aClass instanceClass name, ' class']
  154. ifFalse: [
  155. aClass isNil
  156. ifTrue: ['nil']
  157. ifFalse: [aClass name]]
  158. ! !
  159. Object subclass: #ChunkParser
  160. instanceVariableNames: 'stream'
  161. package: 'Importer-Exporter'!
  162. !ChunkParser commentStamp!
  163. I am responsible for parsing aStream contents in the chunk format.
  164. ## API
  165. ChunkParser new
  166. stream: aStream;
  167. nextChunk!
  168. !ChunkParser methodsFor: 'accessing'!
  169. stream: aStream
  170. stream := aStream
  171. ! !
  172. !ChunkParser methodsFor: 'reading'!
  173. nextChunk
  174. "The chunk format (Smalltalk Interchange Format or Fileout format)
  175. is a trivial format but can be a bit tricky to understand:
  176. - Uses the exclamation mark as delimiter of chunks.
  177. - Inside a chunk a normal exclamation mark must be doubled.
  178. - A non empty chunk must be a valid Smalltalk expression.
  179. - A chunk on top level with a preceding empty chunk is an instruction chunk:
  180. - The object created by the expression then takes over reading chunks.
  181. This metod returns next chunk as a String (trimmed), empty String (all whitespace) or nil."
  182. | char result chunk |
  183. result := '' writeStream.
  184. [char := stream next.
  185. char notNil] whileTrue: [
  186. char = '!!' ifTrue: [
  187. stream peek = '!!'
  188. ifTrue: [stream next "skipping the escape double"]
  189. ifFalse: [^result contents trimBoth "chunk end marker found"]].
  190. result nextPut: char].
  191. ^nil "a chunk needs to end with !!"
  192. ! !
  193. !ChunkParser class methodsFor: 'not yet classified'!
  194. on: aStream
  195. ^self new stream: aStream
  196. ! !
  197. Object subclass: #Exporter
  198. instanceVariableNames: ''
  199. package: 'Importer-Exporter'!
  200. !Exporter commentStamp!
  201. I am responsible for outputting Amber code into a JavaScript string.
  202. The generated output is enough to reconstruct the exported data, including Smalltalk source code and other metadata.
  203. ## Use case
  204. I am typically used to save code outside of the Amber runtime (committing to disk, etc.).
  205. ## API
  206. Use `#exportAll`, `#exportClass:` or `#exportPackage:` methods.!
  207. !Exporter class methodsFor: 'exporting-accessing'!
  208. extensionMethodsOfPackage: package
  209. "Issue #143: sort classes and methods alphabetically"
  210. | name result |
  211. name := package name.
  212. result := OrderedCollection new.
  213. (Package sortedClasses: Smalltalk current classes) do: [:each |
  214. {each. each class} do: [:aClass |
  215. result addAll: (((aClass methodDictionary values)
  216. sorted: [:a :b | a selector <= b selector])
  217. select: [:method | method category match: '^\*', name]) ]].
  218. ^result
  219. !
  220. ownMethodsOfClass: aClass
  221. "Issue #143: sort methods alphabetically"
  222. ^((aClass methodDictionary values) sorted: [:a :b | a selector <= b selector])
  223. reject: [:each | (each category match: '^\*')]
  224. !
  225. ownMethodsOfMetaClass: aClass
  226. "Issue #143: sort methods alphabetically"
  227. ^self ownMethodsOfClass: aClass class
  228. ! !
  229. !Exporter class methodsFor: 'exporting-output'!
  230. exportDefinitionOf: aClass on: aStream
  231. aStream
  232. lf;
  233. nextPutAll: 'smalltalk.addClass(';
  234. nextPutAll: '''', (self classNameFor: aClass), ''', ';
  235. nextPutAll: 'smalltalk.', (self classNameFor: aClass superclass);
  236. nextPutAll: ', ['.
  237. aClass instanceVariableNames
  238. do: [:each | aStream nextPutAll: '''', each, '''']
  239. separatedBy: [aStream nextPutAll: ', '].
  240. aStream
  241. nextPutAll: '], ''';
  242. nextPutAll: aClass category, '''';
  243. nextPutAll: ');'.
  244. aClass comment notEmpty ifTrue: [
  245. aStream
  246. lf;
  247. nextPutAll: 'smalltalk.';
  248. nextPutAll: (self classNameFor: aClass);
  249. nextPutAll: '.comment=';
  250. nextPutAll: aClass comment asJavascript;
  251. nextPutAll: ';'].
  252. aStream lf
  253. !
  254. exportMetaDefinitionOf: aClass on: aStream
  255. aStream lf.
  256. aClass class instanceVariableNames isEmpty ifFalse: [
  257. aStream
  258. nextPutAll: 'smalltalk.', (self classNameFor: aClass class);
  259. nextPutAll: '.iVarNames = ['.
  260. aClass class instanceVariableNames
  261. do: [:each | aStream nextPutAll: '''', each, '''']
  262. separatedBy: [aStream nextPutAll: ','].
  263. aStream nextPutAll: '];', String lf]
  264. !
  265. exportMethod: aMethod on: aStream
  266. aStream
  267. nextPutAll: 'smalltalk.addMethod(';lf;
  268. "nextPutAll: aMethod selector asSelector asJavascript, ',';lf;"
  269. nextPutAll: 'smalltalk.method({';lf;
  270. nextPutAll: 'selector: ', aMethod selector asJavascript, ',';lf;
  271. nextPutAll: 'category: ''', aMethod category, ''',';lf;
  272. nextPutAll: 'fn: ', aMethod fn compiledSource, ',';lf;
  273. nextPutAll: 'args: ', aMethod arguments asJavascript, ','; lf;
  274. nextPutAll: 'source: ', aMethod source asJavascript, ',';lf;
  275. nextPutAll: 'messageSends: ', aMethod messageSends asJavascript, ',';lf;
  276. nextPutAll: 'referencedClasses: ', aMethod referencedClasses asJavascript.
  277. aStream
  278. lf;
  279. nextPutAll: '}),';lf;
  280. nextPutAll: 'smalltalk.', (self classNameFor: aMethod methodClass);
  281. nextPutAll: ');';lf;lf
  282. !
  283. exportPackageDefinitionOf: package on: aStream
  284. aStream
  285. nextPutAll: 'smalltalk.addPackage(';
  286. nextPutAll: '''', package name, ''');';
  287. lf
  288. !
  289. exportPackageEpilogueOf: aPackage on: aStream
  290. aStream
  291. nextPutAll: '})(global_smalltalk,global_nil,global__st);';
  292. lf
  293. !
  294. exportPackagePrologueOf: aPackage on: aStream
  295. aStream
  296. nextPutAll: '(function(smalltalk,nil,_st){';
  297. lf
  298. ! !
  299. !Exporter class methodsFor: 'fileOut'!
  300. amdRecipe
  301. "Export a given package with amd transport type."
  302. | legacy |
  303. legacy := self recipe.
  304. ^(legacy copyFrom: 1 to: 2),
  305. { AmdExporter -> #exportPackageTransportOf:on: },
  306. (legacy copyFrom: 3 to: legacy size)
  307. !
  308. recipe
  309. "Export a given package."
  310. ^{
  311. AmdExporter -> #exportPackagePrologueOf:on:.
  312. self -> #exportPackageDefinitionOf:on:.
  313. {
  314. PluggableExporter -> #ownClassesOfPackage:.
  315. self -> #exportDefinitionOf:on:.
  316. {
  317. self -> #ownMethodsOfClass:.
  318. self -> #exportMethod:on: }.
  319. self -> #exportMetaDefinitionOf:on:.
  320. {
  321. self -> #ownMethodsOfMetaClass:.
  322. self -> #exportMethod:on: } }.
  323. {
  324. self -> #extensionMethodsOfPackage:.
  325. self -> #exportMethod:on: }.
  326. AmdExporter -> #exportPackageEpilogueOf:on:
  327. }
  328. ! !
  329. !Exporter class methodsFor: 'private'!
  330. classNameFor: aClass
  331. ^aClass isMetaclass
  332. ifTrue: [aClass instanceClass name, '.klass']
  333. ifFalse: [
  334. aClass isNil
  335. ifTrue: ['nil']
  336. ifFalse: [aClass name]]
  337. ! !
  338. Exporter subclass: #StrippedExporter
  339. instanceVariableNames: ''
  340. package: 'Importer-Exporter'!
  341. !StrippedExporter commentStamp!
  342. I export Amber code into a JavaScript string, but without any optional associated data like the Amber source code.!
  343. !StrippedExporter class methodsFor: 'exporting-output'!
  344. exportDefinitionOf: aClass on: aStream
  345. aStream
  346. lf;
  347. nextPutAll: 'smalltalk.addClass(';
  348. nextPutAll: '''', (self classNameFor: aClass), ''', ';
  349. nextPutAll: 'smalltalk.', (self classNameFor: aClass superclass);
  350. nextPutAll: ', ['.
  351. aClass instanceVariableNames
  352. do: [:each | aStream nextPutAll: '''', each, '''']
  353. separatedBy: [aStream nextPutAll: ', '].
  354. aStream
  355. nextPutAll: '], ''';
  356. nextPutAll: aClass category, '''';
  357. nextPutAll: ');'.
  358. aStream lf
  359. !
  360. exportMethod: aMethod on: aStream
  361. aStream
  362. nextPutAll: 'smalltalk.addMethod(';lf;
  363. "nextPutAll: aMethod selector asSelector asJavascript, ',';lf;"
  364. nextPutAll: 'smalltalk.method({';lf;
  365. nextPutAll: 'selector: ', aMethod selector asJavascript, ',';lf;
  366. nextPutAll: 'fn: ', aMethod fn compiledSource, ',';lf;
  367. nextPutAll: 'messageSends: ', aMethod messageSends asJavascript;
  368. nextPutAll: '}),';lf;
  369. nextPutAll: 'smalltalk.', (self classNameFor: aMethod methodClass);
  370. nextPutAll: ');';lf;lf
  371. ! !
  372. Object subclass: #Importer
  373. instanceVariableNames: ''
  374. package: 'Importer-Exporter'!
  375. !Importer commentStamp!
  376. I can import Amber code from a string in the chunk format.
  377. ## API
  378. Importer new import: aString!
  379. !Importer methodsFor: 'fileIn'!
  380. import: aStream
  381. | chunk result parser lastEmpty |
  382. parser := ChunkParser on: aStream.
  383. lastEmpty := false.
  384. [chunk := parser nextChunk.
  385. chunk isNil] whileFalse: [
  386. chunk isEmpty
  387. ifTrue: [lastEmpty := true]
  388. ifFalse: [
  389. result := Compiler new evaluateExpression: chunk.
  390. lastEmpty
  391. ifTrue: [
  392. lastEmpty := false.
  393. result scanFrom: parser]]]
  394. ! !
  395. Object subclass: #MethodCategory
  396. instanceVariableNames: 'methods name klass'
  397. package: 'Importer-Exporter'!
  398. !MethodCategory methodsFor: 'accessing'!
  399. klass
  400. ^klass
  401. !
  402. klass: aClass
  403. klass := aClass
  404. !
  405. methods
  406. ^methods
  407. !
  408. methods: anArray
  409. methods := anArray
  410. !
  411. name
  412. ^name
  413. !
  414. name: aString
  415. name := aString
  416. ! !
  417. !MethodCategory class methodsFor: 'not yet classified'!
  418. name: aString class: aClass methods: anArray
  419. ^self new
  420. name: aString;
  421. klass: aClass;
  422. methods: anArray;
  423. yourself
  424. ! !
  425. InterfacingObject subclass: #PackageHandler
  426. instanceVariableNames: ''
  427. package: 'Importer-Exporter'!
  428. !PackageHandler commentStamp!
  429. I am responsible for handling package loading and committing.
  430. I should not be used directly. Instead, use the corresponding `Package` methods.!
  431. !PackageHandler methodsFor: 'committing'!
  432. commit: aPackage
  433. self commitChannels
  434. do: [ :commitStrategyFactory || fileContents commitStrategy |
  435. commitStrategy := commitStrategyFactory value: aPackage.
  436. fileContents := String streamContents: [ :stream |
  437. (PluggableExporter newUsing: commitStrategy key) exportPackage: aPackage on: stream ].
  438. self ajaxPutAt: commitStrategy value data: fileContents ]
  439. displayingProgress: 'Committing package ', aPackage name
  440. !
  441. commitChannels
  442. self subclassResponsibility
  443. ! !
  444. !PackageHandler methodsFor: 'private'!
  445. ajaxPutAt: aURL data: aString
  446. self
  447. ajax: #{
  448. 'url' -> aURL.
  449. 'type' -> 'PUT'.
  450. 'data' -> aString.
  451. 'contentType' -> 'text/plain;charset=UTF-8'.
  452. 'error' -> [ :xhr | self error: 'Commiting ' , aURL , ' failed with reason: "' , (xhr responseText) , '"'] }
  453. ! !
  454. PackageHandler class instanceVariableNames: 'registry'!
  455. !PackageHandler class methodsFor: 'accessing'!
  456. classRegisteredFor: aString
  457. ^registry at: aString
  458. !
  459. for: aString
  460. ^(self classRegisteredFor: aString) new
  461. ! !
  462. !PackageHandler class methodsFor: 'initialization'!
  463. initialize
  464. super initialize.
  465. registry := #{}
  466. ! !
  467. !PackageHandler class methodsFor: 'registry'!
  468. register: aClass for: aString
  469. registry at: aString put: aClass
  470. !
  471. registerFor: aString
  472. PackageHandler register: self for: aString
  473. ! !
  474. PackageHandler subclass: #AmdPackageHandler
  475. instanceVariableNames: ''
  476. package: 'Importer-Exporter'!
  477. !AmdPackageHandler commentStamp!
  478. I am responsible for handling package loading and committing.
  479. I should not be used directly. Instead, use the corresponding `Package` methods.!
  480. !AmdPackageHandler methodsFor: 'committing'!
  481. commitChannels
  482. ^{
  483. [ :pkg | Exporter amdRecipe -> (pkg commitPathJs, '/', pkg name, '.js') ].
  484. [ :pkg | StrippedExporter amdRecipe -> (pkg commitPathJs, '/', pkg name, '.deploy.js') ].
  485. [ :pkg | ChunkExporter recipe -> (pkg commitPathSt, '/', pkg name, '.st') ]
  486. }
  487. !
  488. commitPathJsFor: aPackage
  489. ^self toUrl: (self namespaceFor: aPackage)
  490. !
  491. commitPathStFor: aPackage
  492. "if _source is not mapped, .st commit will likely fail"
  493. ^self toUrl: (self namespaceFor: aPackage), '/_source'.
  494. !
  495. namespaceFor: aPackage
  496. ^aPackage amdNamespace
  497. ifNil: [ aPackage amdNamespace: self class defaultNamespace; amdNamespace ]
  498. ! !
  499. !AmdPackageHandler methodsFor: 'private'!
  500. toUrl: aString
  501. (Smalltalk current at: '_amd_require')
  502. ifNil: [ self error: 'AMD loader not present' ]
  503. ifNotNil: [ :require | ^(require basicAt: 'toUrl') value: aString ]
  504. ! !
  505. AmdPackageHandler class instanceVariableNames: 'defaultNamespace'!
  506. !AmdPackageHandler class methodsFor: 'commit paths'!
  507. commitPathsFromLoader
  508. "TODO"
  509. !
  510. defaultNamespace
  511. ^ defaultNamespace ifNil: [ self error: 'AMD default namespace not set.' ]
  512. !
  513. defaultNamespace: aString
  514. defaultNamespace := aString
  515. !
  516. resetCommitPaths
  517. defaultNamespace := nil
  518. ! !
  519. !AmdPackageHandler class methodsFor: 'initialization'!
  520. initialize
  521. super initialize.
  522. self registerFor: 'amd'.
  523. self commitPathsFromLoader
  524. ! !
  525. PackageHandler subclass: #LegacyPackageHandler
  526. instanceVariableNames: ''
  527. package: 'Importer-Exporter'!
  528. !LegacyPackageHandler commentStamp!
  529. I am responsible for handling package loading and committing.
  530. I should not be used directly. Instead, use the corresponding `Package` methods.!
  531. !LegacyPackageHandler methodsFor: 'committing'!
  532. commitChannels
  533. ^{
  534. [ :pkg | Exporter recipe -> (pkg commitPathJs, '/', pkg name, '.js') ].
  535. [ :pkg | StrippedExporter recipe -> (pkg commitPathJs, '/', pkg name, '.deploy.js') ].
  536. [ :pkg | ChunkExporter recipe -> (pkg commitPathSt, '/', pkg name, '.st') ]
  537. }
  538. !
  539. commitPathJsFor: aPackage
  540. ^self class defaultCommitPathJs
  541. !
  542. commitPathStFor: aPackage
  543. ^self class defaultCommitPathSt
  544. ! !
  545. !LegacyPackageHandler methodsFor: 'loading'!
  546. loadPackage: packageName prefix: aString
  547. | url |
  548. url := '/', aString, '/js/', packageName, '.js'.
  549. self
  550. ajax: #{
  551. 'url' -> url.
  552. 'type' -> 'GET'.
  553. 'dataType' -> 'script'.
  554. 'complete' -> [ :jqXHR :textStatus |
  555. jqXHR readyState = 4
  556. ifTrue: [ self setupPackageNamed: packageName prefix: aString ] ].
  557. 'error' -> [ self alert: 'Could not load package at: ', url ]
  558. }
  559. !
  560. loadPackages: aCollection prefix: aString
  561. aCollection do: [ :each |
  562. self loadPackage: each prefix: aString ]
  563. ! !
  564. !LegacyPackageHandler methodsFor: 'private'!
  565. setupPackageNamed: packageName prefix: aString
  566. (Package named: packageName)
  567. setupClasses;
  568. commitPathJs: '/', aString, '/js';
  569. commitPathSt: '/', aString, '/st'
  570. ! !
  571. LegacyPackageHandler class instanceVariableNames: 'defaultCommitPathJs defaultCommitPathSt'!
  572. !LegacyPackageHandler class methodsFor: 'commit paths'!
  573. commitPathsFromLoader
  574. <
  575. var commitPath = typeof amber !!== 'undefined' && amber.commitPath;
  576. if (!!commitPath) return;
  577. if (commitPath.js) self._defaultCommitPathJs_(commitPath.js);
  578. if (commitPath.st) self._defaultCommitPathSt_(commitPath.st);
  579. >
  580. !
  581. defaultCommitPathJs
  582. ^ defaultCommitPathJs ifNil: [ defaultCommitPathJs := 'js']
  583. !
  584. defaultCommitPathJs: aString
  585. defaultCommitPathJs := aString
  586. !
  587. defaultCommitPathSt
  588. ^ defaultCommitPathSt ifNil: [ defaultCommitPathSt := 'st']
  589. !
  590. defaultCommitPathSt: aString
  591. defaultCommitPathSt := aString
  592. !
  593. resetCommitPaths
  594. defaultCommitPathJs := nil.
  595. defaultCommitPathSt := nil
  596. ! !
  597. !LegacyPackageHandler class methodsFor: 'initialization'!
  598. initialize
  599. super initialize.
  600. self registerFor: 'unknown'.
  601. self commitPathsFromLoader
  602. ! !
  603. !LegacyPackageHandler class methodsFor: 'loading'!
  604. loadPackages: aCollection prefix: aString
  605. ^ self new loadPackages: aCollection prefix: aString
  606. ! !
  607. Object subclass: #PluggableExporter
  608. instanceVariableNames: 'recipe'
  609. package: 'Importer-Exporter'!
  610. !PluggableExporter methodsFor: 'accessing'!
  611. recipe
  612. ^recipe
  613. !
  614. recipe: anArray
  615. recipe := anArray
  616. ! !
  617. !PluggableExporter methodsFor: 'fileOut'!
  618. export: anObject usingRecipe: anArray on: aStream
  619. | args |
  620. args := { anObject. aStream }.
  621. anArray do: [ :each | | val |
  622. val := each value.
  623. val == each
  624. ifFalse: [ "association"
  625. each key perform: val withArguments: args ]
  626. ifTrue: [ "sub-array"
  627. | selection |
  628. selection := each first key perform: each first value withArguments: { anObject }.
  629. selection do: [ :eachPart | self export: eachPart usingRecipe: each allButFirst on: aStream ]]]
  630. !
  631. exportAll
  632. "Export all packages in the system."
  633. ^String streamContents: [:stream |
  634. Smalltalk current packages do: [:pkg |
  635. self exportPackage: pkg on: stream]]
  636. !
  637. exportPackage: aPackage on: aStream
  638. self export: aPackage usingRecipe: self recipe on: aStream
  639. ! !
  640. !PluggableExporter class methodsFor: 'exporting-accessing'!
  641. newUsing: recipe
  642. ^self new recipe: recipe; yourself
  643. !
  644. ownClassesOfPackage: package
  645. "Export classes in dependency order.
  646. Update (issue #171): Remove duplicates for export"
  647. ^package sortedClasses asSet
  648. ! !
  649. !Package methodsFor: '*Importer-Exporter'!
  650. amdNamespace
  651. <return (self.transport && self.transport.amdNamespace) || nil>
  652. !
  653. amdNamespace: aString
  654. <
  655. if (!!self.transport) { self.transport = { type: 'amd' }; }
  656. if (self.transport.type !!== 'amd') { throw new Error('Package '+self._name()+' has transport type '+self.transport.type+', not "amd".'); }
  657. self.transport.amdNamespace = aString;
  658. >
  659. !
  660. commit
  661. ^ self transport commit: self
  662. !
  663. commitPathJs
  664. ^ (extension ifNil: [ extension := #{} ]) at: #commitPathJs ifAbsent: [self transport commitPathJsFor: self]
  665. !
  666. commitPathJs: aString
  667. ^ (extension ifNil: [ extension := #{} ]) at: #commitPathJs put: aString
  668. !
  669. commitPathSt
  670. ^ (extension ifNil: [ extension := #{} ]) at: #commitPathSt ifAbsent: [self transport commitPathStFor: self]
  671. !
  672. commitPathSt: aString
  673. ^ (extension ifNil: [ extension := #{} ]) at: #commitPathSt put: aString
  674. !
  675. loadDependencies
  676. "Returns list of packages that need to be present
  677. before loading this package.
  678. These are determined as set of packages covering
  679. all classes used either for subclassing or for defining
  680. extension methods on."
  681. "Fake one for now. TODO"
  682. | root |
  683. root := Object package.
  684. self == root ifTrue: [ ^#() ] ifFalse: [ ^{root} ]
  685. !
  686. transport
  687. ^ PackageHandler for: self transportType
  688. !
  689. transportJson
  690. <return JSON.stringify(self.transport || null);>
  691. !
  692. transportType
  693. <return (self.transport && self.transport.type) || 'unknown';>
  694. ! !