Importer-Exporter.st 21 KB

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