Importer-Exporter.st 27 KB

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