Importer-Exporter.st 14 KB

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