Importer-Exporter.st 25 KB

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