Importer-Exporter.st 16 KB

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