Importer-Exporter.st 14 KB

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