Importer-Exporter.st 21 KB

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