Importer-Exporter.st 18 KB

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