Importer-Exporter.st 15 KB

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