Platform-ImportExport.st 26 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122
  1. Smalltalk createPackage: 'Platform-ImportExport'!
  2. Object subclass: #AbstractExporter
  3. instanceVariableNames: ''
  4. package: 'Platform-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
  37. ifNil: [ 'nil' ]
  38. ifNotNil: [ aClass name ] ]
  39. ! !
  40. !AbstractExporter methodsFor: 'output'!
  41. exportPackage: aPackage on: aStream
  42. self subclassResponsibility
  43. ! !
  44. AbstractExporter subclass: #ChunkExporter
  45. instanceVariableNames: ''
  46. package: 'Platform-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 ifNotEmpty: [
  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 ifNotEmpty: [ :classIvars |
  118. aStream
  119. nextPutAll: (self classNameFor: aClass class);
  120. nextPutAll: ' instanceVariableNames: '''.
  121. classIvars
  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: (self chunkEscape: 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: 'Platform-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 ifNotEmpty: [
  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 ifNotEmpty: [ :classIvars |
  240. aStream
  241. nextPutAll: (self jsClassNameFor: aClass class);
  242. nextPutAll: '.iVarNames = ['.
  243. classIvars
  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. exportPackageBodyBlockPrologueOf: aPackage on: aStream
  284. aStream
  285. nextPutAll: 'if(!!$boot.nilAsReceiver)$boot.nilAsReceiver=$boot.nil;';
  286. lf;
  287. nextPutAll: 'var $core=$boot.api,nil=$boot.nilAsReceiver,$recv=$boot.asReceiver,$globals=$boot.globals;';
  288. lf;
  289. nextPutAll: 'if(!!$boot.nilAsClass)$boot.nilAsClass=$boot.dnu;';
  290. lf
  291. !
  292. exportPackageContextOf: aPackage on: aStream
  293. aStream
  294. nextPutAll: '$core.packages[';
  295. nextPutAll: aPackage name asJavascript;
  296. nextPutAll: '].innerEval = ';
  297. nextPutAll: 'function (expr) { return eval(expr); }';
  298. nextPutAll: ';';
  299. lf
  300. !
  301. exportPackageDefinitionOf: aPackage on: aStream
  302. aStream
  303. nextPutAll: '$core.addPackage(';
  304. nextPutAll: '''', aPackage name, ''');';
  305. lf
  306. !
  307. exportPackageEpilogueOf: aPackage on: aStream
  308. self subclassResponsibility
  309. !
  310. exportPackageImportsOf: aPackage on: aStream
  311. aPackage importsAsJson ifNotEmpty: [ :imports |
  312. aStream
  313. nextPutAll: '$core.packages[';
  314. nextPutAll: aPackage name asJavascript;
  315. nextPutAll: '].imports = ';
  316. nextPutAll: imports asJavascript;
  317. nextPutAll: ';';
  318. lf ]
  319. !
  320. exportPackagePrologueOf: aPackage on: aStream
  321. self subclassResponsibility
  322. !
  323. exportPackageTransportOf: aPackage on: aStream
  324. aStream
  325. nextPutAll: '$core.packages[';
  326. nextPutAll: aPackage name asJavascript;
  327. nextPutAll: '].transport = ';
  328. nextPutAll: aPackage transport asJSONString;
  329. nextPutAll: ';';
  330. lf
  331. ! !
  332. Exporter subclass: #AmdExporter
  333. instanceVariableNames: 'namespace'
  334. package: 'Platform-ImportExport'!
  335. !AmdExporter commentStamp!
  336. I am used to export Packages in an AMD (Asynchronous Module Definition) JavaScript format.!
  337. !AmdExporter methodsFor: 'output'!
  338. exportPackageEpilogueOf: aPackage on: aStream
  339. aStream
  340. nextPutAll: '});';
  341. lf
  342. !
  343. exportPackagePrologueOf: aPackage on: aStream
  344. | importsForOutput loadDependencies pragmaStart pragmaEnd |
  345. pragmaStart := ''.
  346. pragmaEnd := ''.
  347. importsForOutput := self importsForOutput: aPackage.
  348. loadDependencies := self amdNamesOfPackages: aPackage loadDependencies.
  349. importsForOutput value ifNotEmpty: [
  350. pragmaStart := String lf, '//>>excludeStart("imports", pragmas.excludeImports);', String lf.
  351. pragmaEnd := String lf, '//>>excludeEnd("imports");', String lf ].
  352. aStream
  353. nextPutAll: 'define(';
  354. nextPutAll: (((
  355. (#('amber/boot' ':1:'), importsForOutput value, #(':2:'), loadDependencies asArray sorted) asJavascript)
  356. replace: ',\s*["'']:1:["'']' with: pragmaStart) replace: ',\s*["'']:2:["'']' with: pragmaEnd);
  357. nextPutAll: ', function(';
  358. nextPutAll: (((
  359. (#('$boot' ':1:'), importsForOutput key, #(':2:')) join: ',')
  360. replace: ',\s*:1:' with: pragmaStart) replace: ',\s*:2:' with: pragmaEnd);
  361. nextPutAll: '){"use strict";';
  362. lf.
  363. self exportPackageBodyBlockPrologueOf: aPackage on: aStream
  364. ! !
  365. !AmdExporter methodsFor: 'private'!
  366. amdNamesOfPackages: anArray
  367. ^ (anArray
  368. select: [ :each | (self amdNamespaceOfPackage: each) notNil ])
  369. collect: [ :each | (self amdNamespaceOfPackage: each), '/', each name ]
  370. !
  371. amdNamespaceOfPackage: aPackage
  372. ^ (aPackage transport type = 'amd')
  373. ifTrue: [ aPackage transport namespace ]
  374. ifFalse: [ nil ]
  375. !
  376. importsForOutput: aPackage
  377. "Returns an association where key is list of import variables
  378. and value is list of external dependencies, with ones imported as variables
  379. put at the beginning with same order as is in key.
  380. For example imports:{'jQuery'->'jquery'. 'bootstrap'} would yield
  381. #('jQuery') -> #('jquery' 'bootstrap')"
  382. | namedImports anonImports importVarNames |
  383. namedImports := #().
  384. anonImports := #().
  385. importVarNames := #().
  386. aPackage imports do: [ :each | each isString
  387. ifTrue: [ anonImports add: each ]
  388. ifFalse: [ namedImports add: each value.
  389. importVarNames add: each key ]].
  390. ^ importVarNames -> (namedImports, anonImports)
  391. ! !
  392. Object subclass: #ChunkParser
  393. instanceVariableNames: 'stream last'
  394. package: 'Platform-ImportExport'!
  395. !ChunkParser commentStamp!
  396. I am responsible for parsing aStream contents in the chunk format.
  397. ## API
  398. ChunkParser new
  399. stream: aStream;
  400. nextChunk!
  401. !ChunkParser methodsFor: 'accessing'!
  402. last
  403. ^ last
  404. !
  405. stream: aStream
  406. stream := aStream
  407. ! !
  408. !ChunkParser methodsFor: 'reading'!
  409. nextChunk
  410. "The chunk format (Smalltalk Interchange Format or Fileout format)
  411. is a trivial format but can be a bit tricky to understand:
  412. - Uses the exclamation mark as delimiter of chunks.
  413. - Inside a chunk a normal exclamation mark must be doubled.
  414. - A non empty chunk must be a valid Smalltalk expression.
  415. - A chunk on top level with a preceding empty chunk is an instruction chunk:
  416. - The object created by the expression then takes over reading chunks.
  417. This method returns next chunk as a String (trimmed), empty String (all whitespace) or nil."
  418. | char result chunk |
  419. result := '' writeStream.
  420. [ char := stream next.
  421. char notNil ] whileTrue: [
  422. char = '!!' ifTrue: [
  423. stream peek = '!!'
  424. ifTrue: [ stream next "skipping the escape double" ]
  425. ifFalse: [ ^ last := result contents trimBoth "chunk end marker found" ]].
  426. result nextPut: char ].
  427. ^ last := nil "a chunk needs to end with !!"
  428. ! !
  429. !ChunkParser class methodsFor: 'instance creation'!
  430. on: aStream
  431. ^ self new stream: aStream
  432. ! !
  433. Object subclass: #ClassCommentReader
  434. instanceVariableNames: 'class'
  435. package: 'Platform-ImportExport'!
  436. !ClassCommentReader commentStamp!
  437. I provide a mechanism for retrieving class comments stored on a file.
  438. See also `ClassCategoryReader`.!
  439. !ClassCommentReader methodsFor: 'accessing'!
  440. class: aClass
  441. class := aClass
  442. ! !
  443. !ClassCommentReader methodsFor: 'fileIn'!
  444. scanFrom: aChunkParser
  445. | chunk |
  446. chunk := aChunkParser nextChunk.
  447. chunk ifNotEmpty: [
  448. self setComment: chunk ].
  449. ! !
  450. !ClassCommentReader methodsFor: 'initialization'!
  451. initialize
  452. super initialize.
  453. ! !
  454. !ClassCommentReader methodsFor: 'private'!
  455. setComment: aString
  456. class comment: aString
  457. ! !
  458. Object subclass: #ClassProtocolReader
  459. instanceVariableNames: 'class category'
  460. package: 'Platform-ImportExport'!
  461. !ClassProtocolReader commentStamp!
  462. I provide a mechanism for retrieving class descriptions stored on a file in the Smalltalk chunk format.!
  463. !ClassProtocolReader methodsFor: 'accessing'!
  464. class: aClass category: aString
  465. class := aClass.
  466. category := aString
  467. ! !
  468. !ClassProtocolReader methodsFor: 'fileIn'!
  469. scanFrom: aChunkParser
  470. | chunk |
  471. [ chunk := aChunkParser nextChunk.
  472. chunk isEmpty ] whileFalse: [
  473. self compileMethod: chunk ]
  474. ! !
  475. !ClassProtocolReader methodsFor: 'initialization'!
  476. initialize
  477. super initialize.
  478. ! !
  479. !ClassProtocolReader methodsFor: 'private'!
  480. compileMethod: aString
  481. Compiler new install: aString forClass: class protocol: category
  482. ! !
  483. Object subclass: #ExportMethodProtocol
  484. instanceVariableNames: 'name theClass'
  485. package: 'Platform-ImportExport'!
  486. !ExportMethodProtocol commentStamp!
  487. I am an abstraction for a method protocol in a class / metaclass.
  488. I know of my class, name and methods.
  489. I am used when exporting a package.!
  490. !ExportMethodProtocol methodsFor: 'accessing'!
  491. methods
  492. ^ (self theClass methodsInProtocol: self name)
  493. sorted: [ :a :b | a selector <= b selector ]
  494. !
  495. name
  496. ^ name
  497. !
  498. name: aString
  499. name := aString
  500. !
  501. theClass
  502. ^ theClass
  503. !
  504. theClass: aClass
  505. theClass := aClass
  506. ! !
  507. !ExportMethodProtocol class methodsFor: 'instance creation'!
  508. name: aString theClass: aClass
  509. ^ self new
  510. name: aString;
  511. theClass: aClass;
  512. yourself
  513. ! !
  514. Object subclass: #Importer
  515. instanceVariableNames: 'lastSection lastChunk'
  516. package: 'Platform-ImportExport'!
  517. !Importer commentStamp!
  518. I can import Amber code from a string in the chunk format.
  519. ## API
  520. Importer new import: aString!
  521. !Importer methodsFor: 'accessing'!
  522. lastChunk
  523. ^ lastChunk
  524. !
  525. lastSection
  526. ^ lastSection
  527. ! !
  528. !Importer methodsFor: 'fileIn'!
  529. import: aStream
  530. | chunk result parser lastEmpty |
  531. parser := ChunkParser on: aStream.
  532. lastEmpty := false.
  533. lastSection := 'n/a, not started'.
  534. lastChunk := nil.
  535. [
  536. [ chunk := parser nextChunk.
  537. chunk isNil ] whileFalse: [
  538. chunk
  539. ifEmpty: [ lastEmpty := true ]
  540. ifNotEmpty: [
  541. lastSection := chunk.
  542. result := Compiler new evaluateExpression: chunk.
  543. lastEmpty
  544. ifTrue: [
  545. lastEmpty := false.
  546. result scanFrom: parser ]] ].
  547. lastSection := 'n/a, finished'
  548. ] on: Error do: [:e | lastChunk := parser last. e resignal ].
  549. ! !
  550. Error subclass: #PackageCommitError
  551. instanceVariableNames: ''
  552. package: 'Platform-ImportExport'!
  553. !PackageCommitError commentStamp!
  554. I get signaled when an attempt to commit a package has failed.!
  555. Object subclass: #PackageHandler
  556. instanceVariableNames: ''
  557. package: 'Platform-ImportExport'!
  558. !PackageHandler commentStamp!
  559. I am responsible for handling package loading and committing.
  560. I should not be used directly. Instead, use the corresponding `Package` methods.!
  561. !PackageHandler methodsFor: 'accessing'!
  562. chunkContentsFor: aPackage
  563. ^ String streamContents: [ :str |
  564. self chunkExporter exportPackage: aPackage on: str ]
  565. !
  566. chunkExporterClass
  567. ^ ChunkExporter
  568. !
  569. commitPathJsFor: aPackage
  570. self subclassResponsibility
  571. !
  572. commitPathStFor: aPackage
  573. self subclassResponsibility
  574. !
  575. contentsFor: aPackage
  576. ^ String streamContents: [ :str |
  577. self exporter exportPackage: aPackage on: str ]
  578. !
  579. exporterClass
  580. self subclassResponsibility
  581. ! !
  582. !PackageHandler methodsFor: 'committing'!
  583. commit: aPackage
  584. self
  585. commit: aPackage
  586. onSuccess: []
  587. onError: [ :error |
  588. PackageCommitError new
  589. messageText: 'Commiting failed with reason: "' , (error responseText) , '"';
  590. signal ]
  591. !
  592. commit: aPackage onSuccess: aBlock onError: anotherBlock
  593. self
  594. commitJsFileFor: aPackage
  595. onSuccess: [
  596. self
  597. commitStFileFor: aPackage
  598. onSuccess: [ aPackage beClean. aBlock value ]
  599. onError: anotherBlock ]
  600. onError: anotherBlock
  601. !
  602. commitJsFileFor: aPackage onSuccess: aBlock onError: anotherBlock
  603. self
  604. ajaxPutAt: (self commitPathJsFor: aPackage), '/', aPackage name, '.js'
  605. data: (self contentsFor: aPackage)
  606. onSuccess: aBlock
  607. onError: anotherBlock
  608. !
  609. commitStFileFor: aPackage onSuccess: aBlock onError: anotherBlock
  610. self
  611. ajaxPutAt: (self commitPathStFor: aPackage), '/', aPackage name, '.st'
  612. data: (self chunkContentsFor: aPackage)
  613. onSuccess: aBlock
  614. onError: anotherBlock
  615. ! !
  616. !PackageHandler methodsFor: 'error handling'!
  617. onCommitError: anError
  618. PackageCommitError new
  619. messageText: 'Commiting failed with reason: "' , (anError responseText) , '"';
  620. signal
  621. ! !
  622. !PackageHandler methodsFor: 'factory'!
  623. chunkExporter
  624. ^ self chunkExporterClass new
  625. !
  626. exporter
  627. ^ self exporterClass new
  628. ! !
  629. !PackageHandler methodsFor: 'loading'!
  630. load: aPackage
  631. self subclassResponsibility
  632. ! !
  633. !PackageHandler methodsFor: 'private'!
  634. ajaxPutAt: aURL data: aString onSuccess: aBlock onError: anotherBlock
  635. | xhr |
  636. xhr := Platform newXhr.
  637. xhr open: 'PUT' url: aURL async: true.
  638. xhr onreadystatechange: [
  639. xhr readyState = 4 ifTrue: [
  640. (xhr status >= 200 and: [ xhr status < 300 ])
  641. ifTrue: aBlock
  642. ifFalse: anotherBlock ]].
  643. xhr send: aString
  644. ! !
  645. PackageHandler subclass: #AmdPackageHandler
  646. instanceVariableNames: ''
  647. package: 'Platform-ImportExport'!
  648. !AmdPackageHandler commentStamp!
  649. I am responsible for handling package loading and committing.
  650. I should not be used directly. Instead, use the corresponding `Package` methods.!
  651. !AmdPackageHandler methodsFor: 'accessing'!
  652. commitPathJsFor: aPackage
  653. ^ self toUrl: (self namespaceFor: aPackage)
  654. !
  655. commitPathStFor: aPackage
  656. "If _source is not mapped, .st will be committed to .js path.
  657. It is recommended not to use _source as it can be deprecated."
  658. | path pathWithout |
  659. path := self toUrl: (self namespaceFor: aPackage), '/_source'.
  660. pathWithout := self commitPathJsFor: aPackage.
  661. ^ path = (pathWithout, '/_source') ifTrue: [ pathWithout ] ifFalse: [ path ]
  662. !
  663. exporterClass
  664. ^ AmdExporter
  665. ! !
  666. !AmdPackageHandler methodsFor: 'committing'!
  667. namespaceFor: aPackage
  668. ^ aPackage transport namespace
  669. ! !
  670. !AmdPackageHandler methodsFor: 'loading'!
  671. load: aPackage
  672. Smalltalk amdRequire
  673. ifNil: [ self error: 'AMD loader not present' ]
  674. ifNotNil: [ :require |
  675. require value: (Array with: (self namespaceFor: aPackage), '/', aPackage name ) ]
  676. ! !
  677. !AmdPackageHandler methodsFor: 'private'!
  678. toUrl: aString
  679. ^ Smalltalk amdRequire
  680. ifNil: [ self error: 'AMD loader not present' ]
  681. ifNotNil: [ :require | (require basicAt: 'toUrl') value: aString ]
  682. ! !
  683. !AmdPackageHandler class methodsFor: 'commit paths'!
  684. defaultNamespace
  685. ^ Smalltalk defaultAmdNamespace
  686. !
  687. defaultNamespace: aString
  688. Smalltalk defaultAmdNamespace: aString
  689. ! !
  690. Object subclass: #PackageTransport
  691. instanceVariableNames: 'package'
  692. package: 'Platform-ImportExport'!
  693. !PackageTransport commentStamp!
  694. I represent the transport mechanism used to commit a package.
  695. My concrete subclasses have a `#handler` to which committing is delegated.!
  696. !PackageTransport methodsFor: 'accessing'!
  697. commitHandlerClass
  698. self subclassResponsibility
  699. !
  700. definition
  701. ^ ''
  702. !
  703. package
  704. ^ package
  705. !
  706. package: aPackage
  707. package := aPackage
  708. !
  709. type
  710. ^ self class type
  711. ! !
  712. !PackageTransport methodsFor: 'committing'!
  713. commit
  714. self commitHandler commit: self package
  715. !
  716. commitOnSuccess: aBlock onError: anotherBlock
  717. self commitHandler
  718. commit: self package
  719. onSuccess: aBlock
  720. onError: anotherBlock
  721. ! !
  722. !PackageTransport methodsFor: 'converting'!
  723. asJSON
  724. ^ #{ 'type' -> self type }
  725. ! !
  726. !PackageTransport methodsFor: 'factory'!
  727. commitHandler
  728. ^ self commitHandlerClass new
  729. ! !
  730. !PackageTransport methodsFor: 'initialization'!
  731. setupFromJson: anObject
  732. "no op. override if needed in subclasses"
  733. ! !
  734. !PackageTransport methodsFor: 'loading'!
  735. load
  736. self commitHandler load: self package
  737. ! !
  738. PackageTransport class instanceVariableNames: 'registry'!
  739. !PackageTransport class methodsFor: 'accessing'!
  740. classRegisteredFor: aString
  741. ^ registry at: aString
  742. !
  743. defaultType
  744. ^ AmdPackageTransport type
  745. !
  746. type
  747. "Override in subclasses"
  748. ^ nil
  749. ! !
  750. !PackageTransport class methodsFor: 'initialization'!
  751. initialize
  752. super initialize.
  753. self == PackageTransport
  754. ifTrue: [ registry := #{} ]
  755. ifFalse: [ self register ]
  756. ! !
  757. !PackageTransport class methodsFor: 'instance creation'!
  758. for: aString
  759. ^ (self classRegisteredFor: aString) new
  760. !
  761. fromJson: anObject
  762. anObject ifNil: [ ^ self for: self defaultType ].
  763. ^ (self for: anObject type)
  764. setupFromJson: anObject;
  765. yourself
  766. ! !
  767. !PackageTransport class methodsFor: 'registration'!
  768. register
  769. PackageTransport register: self
  770. !
  771. register: aClass
  772. aClass type ifNotNil: [
  773. registry at: aClass type put: aClass ]
  774. ! !
  775. PackageTransport subclass: #AmdPackageTransport
  776. instanceVariableNames: 'namespace'
  777. package: 'Platform-ImportExport'!
  778. !AmdPackageTransport commentStamp!
  779. I am the default transport for committing packages.
  780. See `AmdExporter` and `AmdPackageHandler`.!
  781. !AmdPackageTransport methodsFor: 'accessing'!
  782. commitHandlerClass
  783. ^ AmdPackageHandler
  784. !
  785. definition
  786. ^ String streamContents: [ :stream |
  787. stream
  788. nextPutAll: self class name;
  789. nextPutAll: ' namespace: ';
  790. nextPutAll: '''', self namespace, '''' ]
  791. !
  792. namespace
  793. ^ namespace ifNil: [ self defaultNamespace ]
  794. !
  795. namespace: aString
  796. namespace := aString
  797. ! !
  798. !AmdPackageTransport methodsFor: 'actions'!
  799. setPath: aString
  800. "Set the path the the receiver's `namespace`"
  801. (require basicAt: 'config') value: #{
  802. 'paths' -> #{
  803. self namespace -> aString
  804. }
  805. }.
  806. ! !
  807. !AmdPackageTransport methodsFor: 'converting'!
  808. asJSON
  809. ^ super asJSON
  810. at: 'amdNamespace' put: self namespace;
  811. yourself
  812. ! !
  813. !AmdPackageTransport methodsFor: 'defaults'!
  814. defaultNamespace
  815. ^ Smalltalk defaultAmdNamespace
  816. ! !
  817. !AmdPackageTransport methodsFor: 'initialization'!
  818. setupFromJson: anObject
  819. self namespace: (anObject at: 'amdNamespace')
  820. ! !
  821. !AmdPackageTransport methodsFor: 'printing'!
  822. printOn: aStream
  823. super printOn: aStream.
  824. aStream
  825. nextPutAll: ' (AMD Namespace: ';
  826. nextPutAll: self namespace;
  827. nextPutAll: ')'
  828. ! !
  829. !AmdPackageTransport class methodsFor: 'accessing'!
  830. type
  831. ^ 'amd'
  832. ! !
  833. !AmdPackageTransport class methodsFor: 'instance creation'!
  834. namespace: aString
  835. ^ self new
  836. namespace: aString;
  837. yourself
  838. ! !
  839. !Behavior methodsFor: '*Platform-ImportExport'!
  840. commentStamp
  841. ^ ClassCommentReader new
  842. class: self;
  843. yourself
  844. !
  845. commentStamp: aStamp prior: prior
  846. ^ self commentStamp
  847. !
  848. methodsFor: aString
  849. ^ ClassProtocolReader new
  850. class: self category: aString;
  851. yourself
  852. !
  853. methodsFor: aString stamp: aStamp
  854. "Added for file-in compatibility, ignores stamp."
  855. ^ self methodsFor: aString
  856. ! !
  857. !Package methodsFor: '*Platform-ImportExport'!
  858. commit
  859. ^ self transport commit
  860. !
  861. load
  862. ^ self transport load
  863. !
  864. loadFromNamespace: aString
  865. ^ self transport
  866. namespace: aString;
  867. load
  868. ! !
  869. !Package class methodsFor: '*Platform-ImportExport'!
  870. load: aPackageName
  871. (self named: aPackageName) load
  872. !
  873. load: aPackageName fromNamespace: aString
  874. (self named: aPackageName) loadFromNamespace: aString
  875. ! !