Importer-Exporter.st 15 KB

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