Importer-Exporter.st 18 KB

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