Kernel-ImportExport.st 23 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998
  1. Smalltalk createPackage: 'Kernel-ImportExport'!
  2. Object subclass: #AbstractExporter
  3. instanceVariableNames: ''
  4. package: 'Kernel-ImportExport'!
  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 topological sorting (dependency resolution) does not matter here.
  23. Not sorting topologically improves the speed by a number of magnitude.
  24. Not to shuffle diffs, classes are sorted by their name."
  25. (Smalltalk classes asArray sorted: [ :a :b | a name < b name ]) do: [ :each |
  26. {each. each class} do: [ :behavior |
  27. (behavior protocols includes: extensionName) ifTrue: [
  28. result add: (ExportMethodProtocol name: extensionName theClass: behavior) ] ] ].
  29. ^ result
  30. ! !
  31. !AbstractExporter methodsFor: 'convenience'!
  32. classNameFor: aClass
  33. ^ aClass isMetaclass
  34. ifTrue: [ aClass instanceClass name, ' class' ]
  35. ifFalse: [
  36. aClass isNil
  37. ifTrue: [ 'nil' ]
  38. ifFalse: [ aClass name ] ]
  39. ! !
  40. !AbstractExporter methodsFor: 'output'!
  41. exportPackage: aPackage on: aStream
  42. self subclassResponsibility
  43. ! !
  44. AbstractExporter subclass: #ChunkExporter
  45. instanceVariableNames: ''
  46. package: 'Kernel-ImportExport'!
  47. !ChunkExporter commentStamp!
  48. I am an exporter dedicated to outputting Amber source code in the classic Smalltalk chunk format.
  49. I do not output any compiled code.!
  50. !ChunkExporter methodsFor: 'accessing'!
  51. extensionCategoriesOfPackage: aPackage
  52. "Issue #143: sort protocol alphabetically"
  53. | name map result |
  54. name := aPackage name.
  55. result := OrderedCollection new.
  56. (Package sortedClasses: Smalltalk classes) do: [ :each |
  57. {each. each class} do: [ :aClass |
  58. map := Dictionary new.
  59. aClass protocolsDo: [ :category :methods |
  60. category = ('*', name) ifTrue: [ map at: category put: methods ] ].
  61. result addAll: ((map keys sorted: [ :a :b | a <= b ]) collect: [ :category |
  62. MethodCategory name: category theClass: aClass methods: (map at: category) ]) ] ].
  63. ^ result
  64. !
  65. ownCategoriesOfClass: aClass
  66. "Answer the protocols of aClass that are not package extensions"
  67. "Issue #143: sort protocol alphabetically"
  68. | map |
  69. map := Dictionary new.
  70. aClass protocolsDo: [ :each :methods |
  71. (each match: '^\*') ifFalse: [ map at: each put: methods ] ].
  72. ^ (map keys sorted: [ :a :b | a <= b ]) collect: [ :each |
  73. MethodCategory name: each theClass: aClass methods: (map at: each) ]
  74. !
  75. ownCategoriesOfMetaClass: aClass
  76. "Issue #143: sort protocol alphabetically"
  77. ^ self ownCategoriesOfClass: aClass class
  78. !
  79. ownMethodProtocolsOfClass: aClass
  80. "Answer a collection of ExportMethodProtocol object of aClass that are not package extensions"
  81. ^ aClass ownProtocols collect: [ :each |
  82. ExportMethodProtocol name: each theClass: aClass ]
  83. ! !
  84. !ChunkExporter methodsFor: 'convenience'!
  85. chunkEscape: aString
  86. "Replace all occurrences of !! with !!!! and trim at both ends."
  87. ^ (aString replace: '!!' with: '!!!!') trimBoth
  88. ! !
  89. !ChunkExporter methodsFor: 'output'!
  90. exportCategoryEpilogueOf: aCategory on: aStream
  91. aStream nextPutAll: ' !!'; lf; lf
  92. !
  93. exportCategoryPrologueOf: aCategory on: aStream
  94. aStream
  95. nextPutAll: '!!', (self classNameFor: aCategory theClass);
  96. nextPutAll: ' methodsFor: ''', aCategory name, '''!!'
  97. !
  98. exportDefinitionOf: aClass on: aStream
  99. "Chunk format."
  100. aStream
  101. nextPutAll: (self classNameFor: aClass superclass);
  102. nextPutAll: ' subclass: #', (self classNameFor: aClass); lf;
  103. tab; nextPutAll: 'instanceVariableNames: '''.
  104. aClass instanceVariableNames
  105. do: [ :each | aStream nextPutAll: each ]
  106. separatedBy: [ aStream nextPutAll: ' ' ].
  107. aStream
  108. nextPutAll: ''''; lf;
  109. tab; nextPutAll: 'package: ''', aClass category, '''!!'; lf.
  110. aClass comment notEmpty ifTrue: [
  111. aStream
  112. nextPutAll: '!!', (self classNameFor: aClass), ' commentStamp!!';lf;
  113. nextPutAll: (self chunkEscape: aClass comment), '!!';lf ].
  114. aStream lf
  115. !
  116. exportMetaDefinitionOf: aClass on: aStream
  117. aClass class instanceVariableNames isEmpty ifFalse: [
  118. aStream
  119. nextPutAll: (self classNameFor: aClass class);
  120. nextPutAll: ' instanceVariableNames: '''.
  121. aClass class instanceVariableNames
  122. do: [ :each | aStream nextPutAll: each ]
  123. separatedBy: [ aStream nextPutAll: ' ' ].
  124. aStream
  125. nextPutAll: '''!!'; lf; lf ]
  126. !
  127. exportMethod: aMethod on: aStream
  128. aStream
  129. lf; lf; nextPutAll: (self chunkEscape: aMethod source); lf;
  130. nextPutAll: '!!'
  131. !
  132. exportPackage: aPackage on: aStream
  133. self
  134. exportPackageDefinitionOf: aPackage on: aStream;
  135. exportPackageImportsOf: aPackage on: aStream.
  136. aPackage sortedClasses do: [ :each |
  137. self exportDefinitionOf: each on: aStream.
  138. self
  139. exportProtocols: (self ownMethodProtocolsOfClass: each)
  140. on: aStream.
  141. self exportMetaDefinitionOf: each on: aStream.
  142. self
  143. exportProtocols: (self ownMethodProtocolsOfClass: each class)
  144. on: aStream ].
  145. self
  146. exportProtocols: (self extensionProtocolsOfPackage: aPackage)
  147. on: aStream
  148. !
  149. exportPackageDefinitionOf: aPackage on: aStream
  150. aStream
  151. nextPutAll: 'Smalltalk createPackage: ''', aPackage name, '''!!';
  152. lf
  153. !
  154. exportPackageImportsOf: aPackage on: aStream
  155. aPackage imports ifNotEmpty: [ :imports |
  156. aStream
  157. nextPutAll: '(Smalltalk packageAt: ''';
  158. nextPutAll: aPackage name;
  159. nextPutAll: ''') imports: ';
  160. nextPutAll: aPackage importsDefinition;
  161. nextPutAll: '!!';
  162. lf ]
  163. !
  164. exportProtocol: aProtocol on: aStream
  165. self exportProtocolPrologueOf: aProtocol on: aStream.
  166. aProtocol methods do: [ :method |
  167. self exportMethod: method on: aStream ].
  168. self exportProtocolEpilogueOf: aProtocol on: aStream
  169. !
  170. exportProtocolEpilogueOf: aProtocol on: aStream
  171. aStream nextPutAll: ' !!'; lf; lf
  172. !
  173. exportProtocolPrologueOf: aProtocol on: aStream
  174. aStream
  175. nextPutAll: '!!', (self classNameFor: aProtocol theClass);
  176. nextPutAll: ' methodsFor: ''', aProtocol name, '''!!'
  177. !
  178. exportProtocols: aCollection on: aStream
  179. aCollection do: [ :each |
  180. self exportProtocol: each on: aStream ]
  181. ! !
  182. AbstractExporter subclass: #Exporter
  183. instanceVariableNames: ''
  184. package: 'Kernel-ImportExport'!
  185. !Exporter commentStamp!
  186. I am responsible for outputting Amber code into a JavaScript string.
  187. The generated output is enough to reconstruct the exported data, including Smalltalk source code and other metadata.
  188. ## Use case
  189. I am typically used to save code outside of the Amber runtime (committing to disk, etc.).!
  190. !Exporter methodsFor: 'accessing'!
  191. ownMethodsOfClass: aClass
  192. "Issue #143: sort methods alphabetically"
  193. ^ ((aClass methodDictionary values) sorted: [ :a :b | a selector <= b selector ])
  194. reject: [ :each | (each protocol match: '^\*') ]
  195. !
  196. ownMethodsOfMetaClass: aClass
  197. "Issue #143: sort methods alphabetically"
  198. ^ self ownMethodsOfClass: aClass class
  199. ! !
  200. !Exporter methodsFor: 'convenience'!
  201. jsClassNameFor: aClass
  202. ^ aClass isMetaclass
  203. ifTrue: [ (self jsClassNameFor: aClass instanceClass), '.klass' ]
  204. ifFalse: [
  205. aClass
  206. ifNil: [ 'null' ]
  207. ifNotNil: [ '$globals.', aClass name ] ]
  208. ! !
  209. !Exporter methodsFor: 'output'!
  210. exportDefinitionOf: aClass on: aStream
  211. aStream
  212. lf;
  213. nextPutAll: '$core.addClass(';
  214. nextPutAll: '''', (self classNameFor: aClass), ''', ';
  215. nextPutAll: (self jsClassNameFor: aClass superclass);
  216. nextPutAll: ', ['.
  217. aClass instanceVariableNames
  218. do: [ :each | aStream nextPutAll: '''', each, '''' ]
  219. separatedBy: [ aStream nextPutAll: ', ' ].
  220. aStream
  221. nextPutAll: '], ''';
  222. nextPutAll: aClass category, '''';
  223. nextPutAll: ');'.
  224. aClass comment notEmpty ifTrue: [
  225. aStream
  226. lf;
  227. nextPutAll: '//>>excludeStart("ide", pragmas.excludeIdeData);';
  228. lf;
  229. nextPutAll: (self jsClassNameFor: aClass);
  230. nextPutAll: '.comment=';
  231. nextPutAll: aClass comment crlfSanitized asJavascript;
  232. nextPutAll: ';';
  233. lf;
  234. nextPutAll: '//>>excludeEnd("ide");' ].
  235. aStream lf
  236. !
  237. exportMetaDefinitionOf: aClass on: aStream
  238. aStream lf.
  239. aClass class instanceVariableNames isEmpty ifFalse: [
  240. aStream
  241. nextPutAll: (self jsClassNameFor: 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: '$core.addMethod(';lf;
  251. nextPutAll: '$core.method({';lf;
  252. nextPutAll: 'selector: ', aMethod selector asJavascript, ',';lf;
  253. nextPutAll: 'protocol: ''', aMethod protocol, ''',';lf;
  254. nextPutAll: 'fn: ', aMethod fn compiledSource, ',';lf;
  255. nextPutAll: '//>>excludeStart("ide", pragmas.excludeIdeData);';lf;
  256. nextPutAll: 'args: ', aMethod arguments asJavascript, ','; lf;
  257. nextPutAll: 'source: ', aMethod source asJavascript, ',';lf;
  258. nextPutAll: 'referencedClasses: ', aMethod referencedClasses asJavascript, ',';lf;
  259. nextPutAll: '//>>excludeEnd("ide");';lf;
  260. nextPutAll: 'messageSends: ', aMethod messageSends asJavascript;lf;
  261. nextPutAll: '}),';lf;
  262. nextPutAll: (self jsClassNameFor: aMethod methodClass);
  263. nextPutAll: ');';lf;lf
  264. !
  265. exportPackage: aPackage on: aStream
  266. self
  267. exportPackagePrologueOf: aPackage on: aStream;
  268. exportPackageDefinitionOf: aPackage on: aStream;
  269. exportPackageContextOf: aPackage on: aStream;
  270. exportPackageImportsOf: aPackage on: aStream;
  271. exportPackageTransportOf: aPackage on: aStream.
  272. aPackage sortedClasses do: [ :each |
  273. self exportDefinitionOf: each on: aStream.
  274. each ownMethods do: [ :method |
  275. self exportMethod: method on: aStream ].
  276. self exportMetaDefinitionOf: each on: aStream.
  277. each class ownMethods do: [ :method |
  278. self exportMethod: method on: aStream ] ].
  279. (self extensionMethodsOfPackage: aPackage) do: [ :each |
  280. self exportMethod: each on: aStream ].
  281. self exportPackageEpilogueOf: aPackage on: aStream
  282. !
  283. exportPackageContextOf: aPackage on: aStream
  284. aStream
  285. nextPutAll: '$core.packages[';
  286. nextPutAll: aPackage name asJavascript;
  287. nextPutAll: '].innerEval = ';
  288. nextPutAll: 'function (expr) { return eval(expr); }';
  289. nextPutAll: ';';
  290. lf
  291. !
  292. exportPackageDefinitionOf: aPackage on: aStream
  293. aStream
  294. nextPutAll: '$core.addPackage(';
  295. nextPutAll: '''', aPackage name, ''');';
  296. lf
  297. !
  298. exportPackageEpilogueOf: aPackage on: aStream
  299. self subclassResponsibility
  300. !
  301. exportPackageImportsOf: aPackage on: aStream
  302. aPackage importsAsJson ifNotEmpty: [ :imports |
  303. aStream
  304. nextPutAll: '$core.packages[';
  305. nextPutAll: aPackage name asJavascript;
  306. nextPutAll: '].imports = ';
  307. nextPutAll: imports asJavascript;
  308. nextPutAll: ';';
  309. lf ]
  310. !
  311. exportPackagePrologueOf: aPackage on: aStream
  312. self subclassResponsibility
  313. !
  314. exportPackageTransportOf: aPackage on: aStream
  315. aStream
  316. nextPutAll: '$core.packages[';
  317. nextPutAll: aPackage name asJavascript;
  318. nextPutAll: '].transport = ';
  319. nextPutAll: aPackage transport asJSONString;
  320. nextPutAll: ';';
  321. lf
  322. ! !
  323. Exporter subclass: #AmdExporter
  324. instanceVariableNames: 'namespace'
  325. package: 'Kernel-ImportExport'!
  326. !AmdExporter commentStamp!
  327. I am used to export Packages in an AMD (Asynchronous Module Definition) JavaScript format.!
  328. !AmdExporter methodsFor: 'output'!
  329. exportPackageEpilogueOf: aPackage on: aStream
  330. aStream
  331. nextPutAll: '});';
  332. lf
  333. !
  334. exportPackagePrologueOf: aPackage on: aStream
  335. | namedImports anonImports importVarNames loadDependencies |
  336. namedImports := #().
  337. anonImports := #().
  338. importVarNames := #().
  339. aPackage imports do: [ :each | each isString
  340. ifTrue: [ anonImports add: each ]
  341. ifFalse: [ namedImports add: each value.
  342. importVarNames add: each key ]].
  343. loadDependencies := self amdNamesOfPackages: aPackage loadDependencies.
  344. aStream
  345. nextPutAll: 'define("';
  346. nextPutAll: (self amdNamespaceOfPackage: aPackage);
  347. nextPutAll: '/';
  348. nextPutAll: aPackage name;
  349. nextPutAll: '", ';
  350. nextPutAll: (#('amber/boot'), namedImports, anonImports, loadDependencies) asJavascript;
  351. nextPutAll: ', function(';
  352. nextPutAll: (#('$boot'), importVarNames join: ',');
  353. nextPutAll: '){';
  354. lf;
  355. nextPutAll: 'var $core=$boot.api,nil=$boot.nil,$recv=$boot.asReceiver,$globals=$boot.globals;';
  356. lf
  357. ! !
  358. !AmdExporter methodsFor: 'private'!
  359. amdNamesOfPackages: anArray
  360. ^ (anArray
  361. select: [ :each | (self amdNamespaceOfPackage: each) notNil ])
  362. collect: [ :each | (self amdNamespaceOfPackage: each), '/', each name ]
  363. !
  364. amdNamespaceOfPackage: aPackage
  365. ^ (aPackage transport type = 'amd')
  366. ifTrue: [ aPackage transport namespace ]
  367. ifFalse: [ nil ]
  368. ! !
  369. Object subclass: #ChunkParser
  370. instanceVariableNames: 'stream last'
  371. package: 'Kernel-ImportExport'!
  372. !ChunkParser commentStamp!
  373. I am responsible for parsing aStream contents in the chunk format.
  374. ## API
  375. ChunkParser new
  376. stream: aStream;
  377. nextChunk!
  378. !ChunkParser methodsFor: 'accessing'!
  379. last
  380. ^ last
  381. !
  382. stream: aStream
  383. stream := aStream
  384. ! !
  385. !ChunkParser methodsFor: 'reading'!
  386. nextChunk
  387. "The chunk format (Smalltalk Interchange Format or Fileout format)
  388. is a trivial format but can be a bit tricky to understand:
  389. - Uses the exclamation mark as delimiter of chunks.
  390. - Inside a chunk a normal exclamation mark must be doubled.
  391. - A non empty chunk must be a valid Smalltalk expression.
  392. - A chunk on top level with a preceding empty chunk is an instruction chunk:
  393. - The object created by the expression then takes over reading chunks.
  394. This method returns next chunk as a String (trimmed), empty String (all whitespace) or nil."
  395. | char result chunk |
  396. result := '' writeStream.
  397. [ char := stream next.
  398. char notNil ] whileTrue: [
  399. char = '!!' ifTrue: [
  400. stream peek = '!!'
  401. ifTrue: [ stream next "skipping the escape double" ]
  402. ifFalse: [ ^ last := result contents trimBoth "chunk end marker found" ]].
  403. result nextPut: char ].
  404. ^ last := nil "a chunk needs to end with !!"
  405. ! !
  406. !ChunkParser class methodsFor: 'instance creation'!
  407. on: aStream
  408. ^ self new stream: aStream
  409. ! !
  410. Object subclass: #ExportMethodProtocol
  411. instanceVariableNames: 'name theClass'
  412. package: 'Kernel-ImportExport'!
  413. !ExportMethodProtocol commentStamp!
  414. I am an abstraction for a method protocol in a class / metaclass.
  415. I know of my class, name and methods.
  416. I am used when exporting a package.!
  417. !ExportMethodProtocol methodsFor: 'accessing'!
  418. methods
  419. ^ (self theClass methodsInProtocol: self name)
  420. sorted: [ :a :b | a selector <= b selector ]
  421. !
  422. name
  423. ^ name
  424. !
  425. name: aString
  426. name := aString
  427. !
  428. theClass
  429. ^ theClass
  430. !
  431. theClass: aClass
  432. theClass := aClass
  433. ! !
  434. !ExportMethodProtocol class methodsFor: 'instance creation'!
  435. name: aString theClass: aClass
  436. ^ self new
  437. name: aString;
  438. theClass: aClass;
  439. yourself
  440. ! !
  441. Object subclass: #Importer
  442. instanceVariableNames: 'lastSection lastChunk'
  443. package: 'Kernel-ImportExport'!
  444. !Importer commentStamp!
  445. I can import Amber code from a string in the chunk format.
  446. ## API
  447. Importer new import: aString!
  448. !Importer methodsFor: 'accessing'!
  449. lastChunk
  450. ^ lastChunk
  451. !
  452. lastSection
  453. ^ lastSection
  454. ! !
  455. !Importer methodsFor: 'fileIn'!
  456. import: aStream
  457. | chunk result parser lastEmpty |
  458. parser := ChunkParser on: aStream.
  459. lastEmpty := false.
  460. lastSection := 'n/a, not started'.
  461. lastChunk := nil.
  462. [
  463. [ chunk := parser nextChunk.
  464. chunk isNil ] whileFalse: [
  465. chunk isEmpty
  466. ifTrue: [ lastEmpty := true ]
  467. ifFalse: [
  468. lastSection := chunk.
  469. result := Compiler new evaluateExpression: chunk.
  470. lastEmpty
  471. ifTrue: [
  472. lastEmpty := false.
  473. result scanFrom: parser ]] ].
  474. lastSection := 'n/a, finished'
  475. ] on: Error do: [:e | lastChunk := parser last. e signal ].
  476. ! !
  477. InterfacingObject subclass: #PackageHandler
  478. instanceVariableNames: ''
  479. package: 'Kernel-ImportExport'!
  480. !PackageHandler commentStamp!
  481. I am responsible for handling package loading and committing.
  482. I should not be used directly. Instead, use the corresponding `Package` methods.!
  483. !PackageHandler methodsFor: 'accessing'!
  484. chunkContentsFor: aPackage
  485. ^ String streamContents: [ :str |
  486. self chunkExporter exportPackage: aPackage on: str ]
  487. !
  488. chunkExporterClass
  489. ^ ChunkExporter
  490. !
  491. commitPathJsFor: aPackage
  492. self subclassResponsibility
  493. !
  494. commitPathStFor: aPackage
  495. self subclassResponsibility
  496. !
  497. contentsFor: aPackage
  498. ^ String streamContents: [ :str |
  499. self exporter exportPackage: aPackage on: str ]
  500. !
  501. exporterClass
  502. self subclassResponsibility
  503. ! !
  504. !PackageHandler methodsFor: 'committing'!
  505. commit: aPackage
  506. self
  507. commit: aPackage
  508. onSuccess: []
  509. onError: [ :error |
  510. PackageCommitError new
  511. messageText: 'Commiting failed with reason: "' , (error responseText) , '"';
  512. signal ]
  513. !
  514. commit: aPackage onSuccess: aBlock onError: anotherBlock
  515. self
  516. commitJsFileFor: aPackage
  517. onSuccess: [
  518. self
  519. commitStFileFor: aPackage
  520. onSuccess: [ aPackage beClean. aBlock value ]
  521. onError: anotherBlock ]
  522. onError: anotherBlock
  523. !
  524. commitJsFileFor: aPackage onSuccess: aBlock onError: anotherBlock
  525. self
  526. ajaxPutAt: (self commitPathJsFor: aPackage), '/', aPackage name, '.js'
  527. data: (self contentsFor: aPackage)
  528. onSuccess: aBlock
  529. onError: anotherBlock
  530. !
  531. commitStFileFor: aPackage onSuccess: aBlock onError: anotherBlock
  532. self
  533. ajaxPutAt: (self commitPathStFor: aPackage), '/', aPackage name, '.st'
  534. data: (self chunkContentsFor: aPackage)
  535. onSuccess: aBlock
  536. onError: anotherBlock
  537. ! !
  538. !PackageHandler methodsFor: 'error handling'!
  539. onCommitError: anError
  540. PackageCommitError new
  541. messageText: 'Commiting failed with reason: "' , (anError responseText) , '"';
  542. signal
  543. ! !
  544. !PackageHandler methodsFor: 'factory'!
  545. chunkExporter
  546. ^ self chunkExporterClass new
  547. !
  548. exporter
  549. ^ self exporterClass new
  550. ! !
  551. !PackageHandler methodsFor: 'loading'!
  552. load: aPackage
  553. self subclassResponsibility
  554. ! !
  555. !PackageHandler methodsFor: 'private'!
  556. ajaxPutAt: aURL data: aString onSuccess: aBlock onError: anotherBlock
  557. self
  558. ajax: #{
  559. 'url' -> aURL.
  560. 'type' -> 'PUT'.
  561. 'data' -> aString.
  562. 'contentType' -> 'text/plain;charset=UTF-8'.
  563. 'success' -> aBlock.
  564. 'error' -> anotherBlock
  565. }
  566. ! !
  567. PackageHandler subclass: #AmdPackageHandler
  568. instanceVariableNames: ''
  569. package: 'Kernel-ImportExport'!
  570. !AmdPackageHandler commentStamp!
  571. I am responsible for handling package loading and committing.
  572. I should not be used directly. Instead, use the corresponding `Package` methods.!
  573. !AmdPackageHandler methodsFor: 'accessing'!
  574. commitPathJsFor: aPackage
  575. ^ self toUrl: (self namespaceFor: aPackage)
  576. !
  577. commitPathStFor: aPackage
  578. "If _source is not mapped, .st will be committed to .js path.
  579. It is recommended not to use _source as it can be deprecated."
  580. | path pathWithout |
  581. path := self toUrl: (self namespaceFor: aPackage), '/_source'.
  582. pathWithout := self commitPathJsFor: aPackage.
  583. ^ path = (pathWithout, '/_source') ifTrue: [ pathWithout ] ifFalse: [ path ]
  584. !
  585. exporterClass
  586. ^ AmdExporter
  587. ! !
  588. !AmdPackageHandler methodsFor: 'committing'!
  589. namespaceFor: aPackage
  590. ^ aPackage transport namespace
  591. ! !
  592. !AmdPackageHandler methodsFor: 'loading'!
  593. load: aPackage
  594. Smalltalk amdRequire
  595. ifNil: [ self error: 'AMD loader not present' ]
  596. ifNotNil: [ :require |
  597. require value: (Array with: (self namespaceFor: aPackage), '/', aPackage name ) ]
  598. ! !
  599. !AmdPackageHandler methodsFor: 'private'!
  600. toUrl: aString
  601. ^ Smalltalk amdRequire
  602. ifNil: [ self error: 'AMD loader not present' ]
  603. ifNotNil: [ :require | (require basicAt: 'toUrl') value: aString ]
  604. ! !
  605. !AmdPackageHandler class methodsFor: 'commit paths'!
  606. defaultNamespace
  607. ^ Smalltalk defaultAmdNamespace
  608. !
  609. defaultNamespace: aString
  610. Smalltalk defaultAmdNamespace: aString
  611. ! !
  612. Object subclass: #PackageTransport
  613. instanceVariableNames: 'package'
  614. package: 'Kernel-ImportExport'!
  615. !PackageTransport commentStamp!
  616. I represent the transport mechanism used to commit a package.
  617. My concrete subclasses have a `#handler` to which committing is delegated.!
  618. !PackageTransport methodsFor: 'accessing'!
  619. commitHandlerClass
  620. self subclassResponsibility
  621. !
  622. definition
  623. ^ ''
  624. !
  625. package
  626. ^ package
  627. !
  628. package: aPackage
  629. package := aPackage
  630. !
  631. type
  632. ^ self class type
  633. ! !
  634. !PackageTransport methodsFor: 'committing'!
  635. commit
  636. self commitHandler commit: self package
  637. !
  638. commitOnSuccess: aBlock onError: anotherBlock
  639. self commitHandler
  640. commit: self package
  641. onSuccess: aBlock
  642. onError: anotherBlock
  643. ! !
  644. !PackageTransport methodsFor: 'converting'!
  645. asJSON
  646. ^ #{ 'type' -> self type }
  647. ! !
  648. !PackageTransport methodsFor: 'factory'!
  649. commitHandler
  650. ^ self commitHandlerClass new
  651. ! !
  652. !PackageTransport methodsFor: 'initialization'!
  653. setupFromJson: anObject
  654. "no op. override if needed in subclasses"
  655. ! !
  656. !PackageTransport methodsFor: 'loading'!
  657. load
  658. self commitHandler load: self package
  659. ! !
  660. PackageTransport class instanceVariableNames: 'registry'!
  661. !PackageTransport class methodsFor: 'accessing'!
  662. classRegisteredFor: aString
  663. ^ registry at: aString
  664. !
  665. defaultType
  666. ^ AmdPackageTransport type
  667. !
  668. type
  669. "Override in subclasses"
  670. ^ nil
  671. ! !
  672. !PackageTransport class methodsFor: 'initialization'!
  673. initialize
  674. super initialize.
  675. self == PackageTransport
  676. ifTrue: [ registry := #{} ]
  677. ifFalse: [ self register ]
  678. ! !
  679. !PackageTransport class methodsFor: 'instance creation'!
  680. for: aString
  681. ^ (self classRegisteredFor: aString) new
  682. !
  683. fromJson: anObject
  684. anObject ifNil: [ ^ self for: self defaultType ].
  685. ^ (self for: anObject type)
  686. setupFromJson: anObject;
  687. yourself
  688. ! !
  689. !PackageTransport class methodsFor: 'registration'!
  690. register
  691. PackageTransport register: self
  692. !
  693. register: aClass
  694. aClass type ifNotNil: [
  695. registry at: aClass type put: aClass ]
  696. ! !
  697. PackageTransport subclass: #AmdPackageTransport
  698. instanceVariableNames: 'namespace'
  699. package: 'Kernel-ImportExport'!
  700. !AmdPackageTransport commentStamp!
  701. I am the default transport for committing packages.
  702. See `AmdExporter` and `AmdPackageHandler`.!
  703. !AmdPackageTransport methodsFor: 'accessing'!
  704. commitHandlerClass
  705. ^ AmdPackageHandler
  706. !
  707. definition
  708. ^ String streamContents: [ :stream |
  709. stream
  710. nextPutAll: self class name;
  711. nextPutAll: ' namespace: ';
  712. nextPutAll: '''', self namespace, '''' ]
  713. !
  714. namespace
  715. ^ namespace ifNil: [ self defaultNamespace ]
  716. !
  717. namespace: aString
  718. namespace := aString
  719. ! !
  720. !AmdPackageTransport methodsFor: 'actions'!
  721. setPath: aString
  722. "Set the path the the receiver's `namespace`"
  723. (require basicAt: 'config') value: #{
  724. 'paths' -> #{
  725. self namespace -> aString
  726. }
  727. }.
  728. ! !
  729. !AmdPackageTransport methodsFor: 'converting'!
  730. asJSON
  731. ^ super asJSON
  732. at: 'amdNamespace' put: self namespace;
  733. yourself
  734. ! !
  735. !AmdPackageTransport methodsFor: 'defaults'!
  736. defaultNamespace
  737. ^ Smalltalk defaultAmdNamespace
  738. ! !
  739. !AmdPackageTransport methodsFor: 'initialization'!
  740. setupFromJson: anObject
  741. self namespace: (anObject at: 'amdNamespace')
  742. ! !
  743. !AmdPackageTransport methodsFor: 'printing'!
  744. printOn: aStream
  745. super printOn: aStream.
  746. aStream
  747. nextPutAll: ' (AMD Namespace: ';
  748. nextPutAll: self namespace;
  749. nextPutAll: ')'
  750. ! !
  751. !AmdPackageTransport class methodsFor: 'accessing'!
  752. type
  753. ^ 'amd'
  754. ! !
  755. !AmdPackageTransport class methodsFor: 'instance creation'!
  756. namespace: aString
  757. ^ self new
  758. namespace: aString;
  759. yourself
  760. ! !
  761. !Package methodsFor: '*Kernel-ImportExport'!
  762. commit
  763. ^ self transport commit
  764. !
  765. load
  766. ^ self transport load
  767. !
  768. loadFromNamespace: aString
  769. ^ self transport
  770. namespace: aString;
  771. load
  772. ! !
  773. !Package class methodsFor: '*Kernel-ImportExport'!
  774. load: aPackageName
  775. (self named: aPackageName) load
  776. !
  777. load: aPackageName fromNamespace: aString
  778. (self named: aPackageName) loadFromNamespace: aString
  779. ! !