Importer-Exporter.st 16 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598
  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. stream nextPutAll: (self exportPackage: pkg name)]]
  56. !
  57. exportClass: aClass
  58. "Export a single class. Subclasses override these methods."
  59. ^String streamContents: [:stream |
  60. self exportDefinitionOf: aClass on: stream.
  61. self exportMethodsOf: aClass on: stream.
  62. self exportMetaDefinitionOf: aClass on: stream.
  63. self exportMethodsOf: aClass class on: stream]
  64. !
  65. exportPackage: packageName
  66. "Export a given package by name."
  67. | package |
  68. ^String streamContents: [:stream |
  69. package := Smalltalk current packageAt: packageName.
  70. self exportAmdPackagePrologueOf: package on: stream.
  71. [
  72. self exportPackageDefinitionOf: package on: stream.
  73. "Export classes in dependency order.
  74. Update (issue #171): Remove duplicates for export"
  75. package sortedClasses asSet do: [:each |
  76. stream nextPutAll: (self exportClass: each)].
  77. self exportPackageExtensionsOf: package on: stream
  78. ] ensure: [
  79. self exportAmdPackageEpilogueOn: stream
  80. ]]
  81. ! !
  82. !Exporter methodsFor: 'private'!
  83. classNameFor: aClass
  84. ^aClass isMetaclass
  85. ifTrue: [aClass instanceClass name, '.klass']
  86. ifFalse: [
  87. aClass isNil
  88. ifTrue: ['nil']
  89. ifFalse: [aClass name]]
  90. !
  91. exportAmdPackageEpilogueOn: aStream
  92. aStream
  93. nextPutAll: '});';
  94. lf
  95. !
  96. exportAmdPackagePrologueOf: aPackage on: aStream
  97. aStream
  98. nextPutAll: 'define("amber/';
  99. nextPutAll: aPackage name;
  100. nextPutAll: '", ["amber_vm/smalltalk","amber_vm/nil","amber_vm/_st"], function(smalltalk,nil,_st){';
  101. lf
  102. !
  103. exportDefinitionOf: aClass on: aStream
  104. aStream
  105. nextPutAll: 'smalltalk.addClass(';
  106. nextPutAll: '''', (self classNameFor: aClass), ''', ';
  107. nextPutAll: 'smalltalk.', (self classNameFor: aClass superclass);
  108. nextPutAll: ', ['.
  109. aClass instanceVariableNames
  110. do: [:each | aStream nextPutAll: '''', each, '''']
  111. separatedBy: [aStream nextPutAll: ', '].
  112. aStream
  113. nextPutAll: '], ''';
  114. nextPutAll: aClass category, '''';
  115. nextPutAll: ');'.
  116. aClass comment notEmpty ifTrue: [
  117. aStream
  118. lf;
  119. nextPutAll: 'smalltalk.';
  120. nextPutAll: (self classNameFor: aClass);
  121. nextPutAll: '.comment=';
  122. nextPutAll: aClass comment asJavascript;
  123. nextPutAll: ';'].
  124. aStream lf
  125. !
  126. exportMetaDefinitionOf: aClass on: aStream
  127. aClass class instanceVariableNames isEmpty ifFalse: [
  128. aStream
  129. nextPutAll: 'smalltalk.', (self classNameFor: aClass class);
  130. nextPutAll: '.iVarNames = ['.
  131. aClass class instanceVariableNames
  132. do: [:each | aStream nextPutAll: '''', each, '''']
  133. separatedBy: [aStream nextPutAll: ','].
  134. aStream nextPutAll: '];', String lf]
  135. !
  136. exportMethod: aMethod of: aClass on: aStream
  137. aStream
  138. nextPutAll: 'smalltalk.addMethod(';lf;
  139. "nextPutAll: aMethod selector asSelector asJavascript, ',';lf;"
  140. nextPutAll: 'smalltalk.method({';lf;
  141. nextPutAll: 'selector: ', aMethod selector asJavascript, ',';lf;
  142. nextPutAll: 'category: ''', aMethod category, ''',';lf;
  143. nextPutAll: 'fn: ', aMethod fn compiledSource, ',';lf;
  144. nextPutAll: 'args: ', aMethod arguments asJavascript, ','; lf;
  145. nextPutAll: 'source: ', aMethod source asJavascript, ',';lf;
  146. nextPutAll: 'messageSends: ', aMethod messageSends asJavascript, ',';lf;
  147. nextPutAll: 'referencedClasses: ', aMethod referencedClasses asJavascript.
  148. aStream
  149. lf;
  150. nextPutAll: '}),';lf;
  151. nextPutAll: 'smalltalk.', (self classNameFor: aClass);
  152. nextPutAll: ');';lf;lf
  153. !
  154. exportMethodsOf: aClass on: aStream
  155. "Issue #143: sort methods alphabetically"
  156. ((aClass methodDictionary values) sorted: [:a :b | a selector <= b selector]) do: [:each |
  157. (each category match: '^\*') ifFalse: [
  158. self exportMethod: each of: aClass on: aStream]].
  159. aStream lf
  160. !
  161. exportPackageDefinitionOf: package on: aStream
  162. aStream
  163. nextPutAll: 'smalltalk.addPackage(';
  164. nextPutAll: '''', package name, ''');';
  165. lf
  166. !
  167. exportPackageExtensionsOf: package on: aStream
  168. "Issue #143: sort classes and methods alphabetically"
  169. | name |
  170. name := package name.
  171. (Package sortedClasses: Smalltalk current classes) do: [:each |
  172. {each. each class} do: [:aClass |
  173. ((aClass methodDictionary values) sorted: [:a :b | a selector <= b selector]) do: [:method |
  174. (method category match: '^\*', name) ifTrue: [
  175. self exportMethod: method of: aClass on: aStream ]]]]
  176. ! !
  177. Exporter subclass: #ChunkExporter
  178. instanceVariableNames: ''
  179. package: 'Importer-Exporter'!
  180. !ChunkExporter commentStamp!
  181. I am an exporter dedicated to outputting Amber source code in the classic Smalltalk chunk format.
  182. I do not output any compiled code.!
  183. !ChunkExporter methodsFor: 'private'!
  184. chunkEscape: aString
  185. "Replace all occurrences of !! with !!!! and trim at both ends."
  186. ^(aString replace: '!!' with: '!!!!') trimBoth
  187. !
  188. classNameFor: aClass
  189. ^aClass isMetaclass
  190. ifTrue: [aClass instanceClass name, ' class']
  191. ifFalse: [
  192. aClass isNil
  193. ifTrue: ['nil']
  194. ifFalse: [aClass name]]
  195. !
  196. exportAmdPackageEpilogueOn: aStream
  197. !
  198. exportAmdPackagePrologueOf: aPackage on: aStream
  199. !
  200. exportDefinitionOf: aClass on: aStream
  201. "Chunk format."
  202. aStream
  203. nextPutAll: (self classNameFor: aClass superclass);
  204. nextPutAll: ' subclass: #', (self classNameFor: aClass); lf;
  205. tab; nextPutAll: 'instanceVariableNames: '''.
  206. aClass instanceVariableNames
  207. do: [:each | aStream nextPutAll: each]
  208. separatedBy: [aStream nextPutAll: ' '].
  209. aStream
  210. nextPutAll: ''''; lf;
  211. tab; nextPutAll: 'package: ''', aClass category, '''!!'; lf.
  212. aClass comment notEmpty ifTrue: [
  213. aStream
  214. nextPutAll: '!!', (self classNameFor: aClass), ' commentStamp!!';lf;
  215. nextPutAll: (self chunkEscape: aClass comment), '!!';lf].
  216. aStream lf
  217. !
  218. exportMetaDefinitionOf: aClass on: aStream
  219. aClass class instanceVariableNames isEmpty ifFalse: [
  220. aStream
  221. nextPutAll: (self classNameFor: aClass class);
  222. nextPutAll: ' instanceVariableNames: '''.
  223. aClass class instanceVariableNames
  224. do: [:each | aStream nextPutAll: each]
  225. separatedBy: [aStream nextPutAll: ' '].
  226. aStream
  227. nextPutAll: '''!!'; lf; lf]
  228. !
  229. exportMethod: aMethod of: aClass on: aStream
  230. aStream
  231. lf; lf; nextPutAll: (self chunkEscape: aMethod source); lf;
  232. nextPutAll: '!!'
  233. !
  234. exportMethods: methods category: category of: aClass on: aStream
  235. "Issue #143: sort methods alphabetically"
  236. aStream
  237. nextPutAll: '!!', (self classNameFor: aClass);
  238. nextPutAll: ' methodsFor: ''', category, '''!!'.
  239. (methods sorted: [:a :b | a selector <= b selector]) do: [:each |
  240. self exportMethod: each of: aClass on: aStream].
  241. aStream nextPutAll: ' !!'; lf; lf
  242. !
  243. exportMethodsOf: aClass on: aStream
  244. "Issue #143: sort protocol alphabetically"
  245. | map |
  246. map := Dictionary new.
  247. aClass protocolsDo: [:category :methods |
  248. (category match: '^\*') ifFalse: [ map at: category put: methods ]].
  249. (map keys sorted: [:a :b | a <= b ]) do: [:category | | methods |
  250. methods := map at: category.
  251. self
  252. exportMethods: methods
  253. category: category
  254. of: aClass
  255. on: aStream ]
  256. !
  257. exportPackageDefinitionOf: package on: aStream
  258. "Chunk format."
  259. aStream
  260. nextPutAll: 'Smalltalk current createPackage: ''', package name, '''!!';
  261. lf
  262. !
  263. exportPackageExtensionsOf: package on: aStream
  264. "We need to override this one too since we need to group
  265. all methods in a given protocol under a leading methodsFor: chunk
  266. for that class."
  267. "Issue #143: sort protocol alphabetically"
  268. | name map |
  269. name := package name.
  270. (Package sortedClasses: Smalltalk current classes) do: [:each |
  271. {each. each class} do: [:aClass |
  272. map := Dictionary new.
  273. aClass protocolsDo: [:category :methods |
  274. (category match: '^\*', name) ifTrue: [ map at: category put: methods ]].
  275. (map keys sorted: [:a :b | a <= b ]) do: [:category | | methods |
  276. methods := map at: category.
  277. self exportMethods: methods category: category of: aClass on: aStream ]]]
  278. ! !
  279. Exporter subclass: #StrippedExporter
  280. instanceVariableNames: ''
  281. package: 'Importer-Exporter'!
  282. !StrippedExporter commentStamp!
  283. I export Amber code into a JavaScript string, but without any optional associated data like the Amber source code.!
  284. !StrippedExporter methodsFor: 'private'!
  285. exportDefinitionOf: aClass on: aStream
  286. aStream
  287. nextPutAll: 'smalltalk.addClass(';
  288. nextPutAll: '''', (self classNameFor: aClass), ''', ';
  289. nextPutAll: 'smalltalk.', (self classNameFor: aClass superclass);
  290. nextPutAll: ', ['.
  291. aClass instanceVariableNames
  292. do: [:each | aStream nextPutAll: '''', each, '''']
  293. separatedBy: [aStream nextPutAll: ', '].
  294. aStream
  295. nextPutAll: '], ''';
  296. nextPutAll: aClass category, '''';
  297. nextPutAll: ');'.
  298. aStream lf
  299. !
  300. exportMethod: aMethod of: aClass on: aStream
  301. aStream
  302. nextPutAll: 'smalltalk.addMethod(';lf;
  303. "nextPutAll: aMethod selector asSelector asJavascript, ',';lf;"
  304. nextPutAll: 'smalltalk.method({';lf;
  305. nextPutAll: 'selector: ', aMethod selector asJavascript, ',';lf;
  306. nextPutAll: 'fn: ', aMethod fn compiledSource, ',';lf;
  307. nextPutAll: 'messageSends: ', aMethod messageSends asJavascript;
  308. nextPutAll: '}),';lf;
  309. nextPutAll: 'smalltalk.', (self classNameFor: aClass);
  310. nextPutAll: ');';lf;lf
  311. ! !
  312. Object subclass: #Importer
  313. instanceVariableNames: ''
  314. package: 'Importer-Exporter'!
  315. !Importer commentStamp!
  316. I can import Amber code from a string in the chunk format.
  317. ## API
  318. Importer new import: aString!
  319. !Importer methodsFor: 'fileIn'!
  320. import: aStream
  321. | chunk result parser lastEmpty |
  322. parser := ChunkParser on: aStream.
  323. lastEmpty := false.
  324. [chunk := parser nextChunk.
  325. chunk isNil] whileFalse: [
  326. chunk isEmpty
  327. ifTrue: [lastEmpty := true]
  328. ifFalse: [
  329. result := Compiler new evaluateExpression: chunk.
  330. lastEmpty
  331. ifTrue: [
  332. lastEmpty := false.
  333. result scanFrom: parser]]]
  334. ! !
  335. Object subclass: #PackageHandler
  336. instanceVariableNames: ''
  337. package: 'Importer-Exporter'!
  338. !PackageHandler commentStamp!
  339. I am responsible for handling package loading and committing.
  340. I should not be used directly. Instead, use the corresponding `Package` methods.!
  341. !PackageHandler methodsFor: 'committing'!
  342. commit: aPackage
  343. self commitChannels
  344. do: [ :commitStrategyFactory || fileContents commitStrategy |
  345. commitStrategy := commitStrategyFactory value: aPackage.
  346. fileContents := (commitStrategy key exportPackage: aPackage name).
  347. self ajaxPutAt: commitStrategy value data: fileContents ]
  348. displayingProgress: 'Committing package ', aPackage name
  349. ! !
  350. !PackageHandler methodsFor: 'private'!
  351. ajaxPutAt: aURL data: aString
  352. jQuery
  353. ajax: aURL
  354. options: #{
  355. 'type' -> 'PUT'.
  356. 'data' -> aString.
  357. 'contentType' -> 'text/plain;charset=UTF-8'.
  358. 'error' -> [ :xhr | self error: 'Commiting ' , aURL , ' failed with reason: "' , (xhr responseText) , '"'] }
  359. ! !
  360. PackageHandler class instanceVariableNames: 'registry'!
  361. !PackageHandler class methodsFor: 'accessing'!
  362. classRegisteredFor: aString
  363. ^registry at: aString
  364. !
  365. for: aString
  366. ^(self classRegisteredFor: aString) new
  367. ! !
  368. !PackageHandler class methodsFor: 'initialization'!
  369. initialize
  370. super initialize.
  371. registry := #{}
  372. ! !
  373. !PackageHandler class methodsFor: 'registry'!
  374. register: aClass for: aString
  375. registry at: aString put: aClass
  376. !
  377. registerFor: aString
  378. PackageHandler register: self for: aString
  379. ! !
  380. PackageHandler subclass: #LegacyPackageHandler
  381. instanceVariableNames: ''
  382. package: 'Importer-Exporter'!
  383. !LegacyPackageHandler commentStamp!
  384. I am responsible for handling package loading and committing.
  385. I should not be used directly. Instead, use the corresponding `Package` methods.!
  386. !LegacyPackageHandler methodsFor: 'committing'!
  387. commitChannels
  388. ^{
  389. [ :pkg | Exporter new -> (pkg commitPathJs, '/', pkg name, '.js') ].
  390. [ :pkg | StrippedExporter new -> (pkg commitPathJs, '/', pkg name, '.deploy.js') ].
  391. [ :pkg | ChunkExporter new -> (pkg commitPathSt, '/', pkg name, '.st') ]
  392. }
  393. !
  394. commitPathJsFor: aPackage
  395. ^self class defaultCommitPathJs
  396. !
  397. commitPathStFor: aPackage
  398. ^self class defaultCommitPathSt
  399. ! !
  400. !LegacyPackageHandler methodsFor: 'loading'!
  401. loadPackage: packageName prefix: aString
  402. | url |
  403. url := '/', aString, '/js/', packageName, '.js'.
  404. jQuery
  405. ajax: url
  406. options: #{
  407. 'type' -> 'GET'.
  408. 'dataType' -> 'script'.
  409. 'complete' -> [ :jqXHR :textStatus |
  410. jqXHR readyState = 4
  411. ifTrue: [ self setupPackageNamed: packageName prefix: aString ] ].
  412. 'error' -> [ window alert: 'Could not load package at: ', url ]
  413. }
  414. !
  415. loadPackages: aCollection prefix: aString
  416. aCollection do: [ :each |
  417. self loadPackage: each prefix: aString ]
  418. ! !
  419. !LegacyPackageHandler methodsFor: 'private'!
  420. setupPackageNamed: packageName prefix: aString
  421. (Package named: packageName)
  422. setupClasses;
  423. commitPathJs: '/', aString, '/js';
  424. commitPathSt: '/', aString, '/st'
  425. ! !
  426. LegacyPackageHandler class instanceVariableNames: 'defaultCommitPathJs defaultCommitPathSt'!
  427. !LegacyPackageHandler class methodsFor: 'commit paths'!
  428. commitPathsFromLoader
  429. <
  430. var commitPath = typeof amber !!== 'undefined' && amber.commitPath;
  431. if (!!commitPath) return;
  432. if (commitPath.js) self._defaultCommitPathJs_(commitPath.js);
  433. if (commitPath.st) self._defaultCommitPathSt_(commitPath.st);
  434. >
  435. !
  436. defaultCommitPathJs
  437. ^ defaultCommitPathJs ifNil: [ defaultCommitPathJs := 'js']
  438. !
  439. defaultCommitPathJs: aString
  440. defaultCommitPathJs := aString
  441. !
  442. defaultCommitPathSt
  443. ^ defaultCommitPathSt ifNil: [ defaultCommitPathSt := 'st']
  444. !
  445. defaultCommitPathSt: aString
  446. defaultCommitPathSt := aString
  447. !
  448. resetCommitPaths
  449. defaultCommitPathJs := nil.
  450. defaultCommitPathSt := nil
  451. ! !
  452. !LegacyPackageHandler class methodsFor: 'initialization'!
  453. initialize
  454. super initialize.
  455. self registerFor: 'unknown'.
  456. self commitPathsFromLoader
  457. ! !
  458. !LegacyPackageHandler class methodsFor: 'loading'!
  459. loadPackages: aCollection prefix: aString
  460. ^ self new loadPackages: aCollection prefix: aString
  461. ! !
  462. !Package methodsFor: '*Importer-Exporter'!
  463. commit
  464. ^ self transport commit: self
  465. !
  466. commitPathJs
  467. ^ (extension ifNil: [ extension := #{} ]) at: #commitPathJs ifAbsentPut: [self transport commitPathJsFor: self]
  468. !
  469. commitPathJs: aString
  470. ^ (extension ifNil: [ extension := #{} ]) at: #commitPathJs put: aString
  471. !
  472. commitPathSt
  473. ^ (extension ifNil: [ extension := #{} ]) at: #commitPathSt ifAbsentPut: [self transport commitPathStFor: self]
  474. !
  475. commitPathSt: aString
  476. ^ (extension ifNil: [ extension := #{} ]) at: #commitPathSt put: aString
  477. !
  478. transport
  479. ^ PackageHandler for: self transportType
  480. !
  481. transportType
  482. <return (self.transport && self.transport.type) || 'unknown';>
  483. ! !