parser.st 20 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897
  1. Object subclass: #PPParser
  2. instanceVariableNames: 'memo'
  3. category: 'Parser'!
  4. !PPParser methodsFor: 'accessing'!
  5. memo
  6. ^memo
  7. ! !
  8. !PPParser methodsFor: 'error handling'!
  9. onFailure: aBlock
  10. ^PPFailureActionParser on: self block: aBlock
  11. ! !
  12. !PPParser methodsFor: 'initialization'!
  13. initialize
  14. memo := Dictionary new
  15. ! !
  16. !PPParser methodsFor: 'operations'!
  17. , aParser
  18. ^PPSequenceParser with: self with: aParser
  19. !
  20. / aParser
  21. ^PPChoiceParser with: self with: aParser
  22. !
  23. ==> aBlock
  24. ^PPActionParser on: self block: aBlock
  25. !
  26. flatten
  27. ^PPFlattenParser on: self
  28. !
  29. memoizedParse: aStream
  30. | start end node |
  31. start := aStream position.
  32. ^self memo at: start
  33. ifPresent: [:value |
  34. aStream position: (self memo at: start) second.
  35. value first]
  36. ifAbsent: [
  37. node := self parse: aStream.
  38. end := aStream position.
  39. self memo at: start put: (Array with: node with: end).
  40. node]
  41. !
  42. not
  43. ^PPNotParser on: self
  44. !
  45. optional
  46. ^self / PPEpsilonParser new
  47. !
  48. plus
  49. ^PPRepeatingParser on: self min: 1
  50. !
  51. star
  52. ^PPRepeatingParser on: self min: 0
  53. !
  54. withSource
  55. ^PPSourceParser on: self
  56. ! !
  57. !PPParser methodsFor: 'parsing'!
  58. parse: aStream
  59. self subclassResponsibility
  60. !
  61. parseAll: aStream
  62. | result |
  63. result := (PPSequenceParser with: self with: PPEOFParser new) memoizedParse: aStream.
  64. ^result isParseFailure
  65. ifTrue: [self error: (result messageFor: aStream contents)]
  66. ifFalse: [result first]
  67. ! !
  68. PPParser subclass: #PPEOFParser
  69. instanceVariableNames: ''
  70. category: 'Parser'!
  71. !PPEOFParser methodsFor: 'parsing'!
  72. parse: aStream
  73. ^aStream atEnd
  74. ifFalse: [
  75. PPFailure new reason: 'EOF expected' at: aStream position]
  76. ifTrue: [nil]
  77. ! !
  78. PPParser subclass: #PPAnyParser
  79. instanceVariableNames: ''
  80. category: 'Parser'!
  81. !PPAnyParser methodsFor: 'parsing'!
  82. parse: aStream
  83. ^aStream atEnd
  84. ifTrue: [PPFailure new
  85. reason: 'did not expect EOF' at: aStream position]
  86. ifFalse: [aStream next]
  87. ! !
  88. PPParser subclass: #PPEpsilonParser
  89. instanceVariableNames: ''
  90. category: 'Parser'!
  91. !PPEpsilonParser methodsFor: 'parsing'!
  92. parse: aStream
  93. ^nil
  94. ! !
  95. PPParser subclass: #PPStringParser
  96. instanceVariableNames: 'string'
  97. category: 'Parser'!
  98. !PPStringParser methodsFor: 'accessing'!
  99. string
  100. ^string
  101. !
  102. string: aString
  103. string := aString
  104. ! !
  105. !PPStringParser methodsFor: 'parsing'!
  106. parse: aStream
  107. | position result |
  108. position := aStream position.
  109. result := aStream next: self string size.
  110. ^result = self string
  111. ifTrue: [result]
  112. ifFalse: [
  113. aStream position: position.
  114. PPFailure new reason: 'Expected ', self string, ' but got ', (result at: position) printString; yourself]
  115. ! !
  116. PPParser subclass: #PPCharacterParser
  117. instanceVariableNames: 'regexp'
  118. category: 'Parser'!
  119. !PPCharacterParser methodsFor: 'accessing'!
  120. string: aString
  121. regexp := RegularExpression fromString: '[', aString, ']'
  122. ! !
  123. !PPCharacterParser methodsFor: 'parsing'!
  124. parse: aStream
  125. ^(aStream peek notNil and: [self match: aStream peek])
  126. ifTrue: [aStream next]
  127. ifFalse: [PPFailure new reason: 'Could not match' at: aStream position]
  128. ! !
  129. !PPCharacterParser methodsFor: 'private'!
  130. match: aString
  131. ^aString match: regexp
  132. ! !
  133. PPParser subclass: #PPListParser
  134. instanceVariableNames: 'parsers'
  135. category: 'Parser'!
  136. !PPListParser class methodsFor: 'instance creation'!
  137. with: aParser with: anotherParser
  138. ^self withAll: (Array with: aParser with: anotherParser)
  139. !
  140. withAll: aCollection
  141. ^self new
  142. parsers: aCollection;
  143. yourself
  144. ! !
  145. !PPListParser methodsFor: 'accessing'!
  146. parsers
  147. ^parsers ifNil: [#()]
  148. !
  149. parsers: aCollection
  150. parsers := aCollection
  151. ! !
  152. !PPListParser methodsFor: 'copying'!
  153. copyWith: aParser
  154. ^self class withAll: (self parsers copyWith: aParser)
  155. ! !
  156. PPListParser subclass: #PPSequenceParser
  157. instanceVariableNames: ''
  158. category: 'Parser'!
  159. !PPSequenceParser methodsFor: 'copying'!
  160. , aRule
  161. ^self copyWith: aRule
  162. ! !
  163. !PPSequenceParser methodsFor: 'parsing'!
  164. parse: aStream
  165. | start elements element |
  166. start := aStream position.
  167. elements := #().
  168. self parsers
  169. detect: [:each |
  170. element := each memoizedParse: aStream.
  171. elements add: element.
  172. element isParseFailure]
  173. ifNone: [].
  174. ^element isParseFailure
  175. ifFalse: [elements]
  176. ifTrue: [aStream position: start. element]
  177. ! !
  178. PPListParser subclass: #PPChoiceParser
  179. instanceVariableNames: ''
  180. category: 'Parser'!
  181. !PPChoiceParser methodsFor: 'copying'!
  182. / aRule
  183. ^self copyWith: aRule
  184. ! !
  185. !PPChoiceParser methodsFor: 'parsing'!
  186. parse: aStream
  187. | result |
  188. self parsers
  189. detect: [:each |
  190. result := each memoizedParse: aStream.
  191. result isParseFailure not]
  192. ifNone: [].
  193. ^result
  194. ! !
  195. PPParser subclass: #PPDelegateParser
  196. instanceVariableNames: 'parser'
  197. category: 'Parser'!
  198. !PPDelegateParser class methodsFor: 'instance creation'!
  199. on: aParser
  200. ^self new
  201. parser: aParser;
  202. yourself
  203. ! !
  204. !PPDelegateParser methodsFor: 'accessing'!
  205. parser
  206. ^parser
  207. !
  208. parser: aParser
  209. parser := aParser
  210. ! !
  211. !PPDelegateParser methodsFor: 'parsing'!
  212. parse: aStream
  213. ^self parser memoizedParse: aStream
  214. ! !
  215. PPDelegateParser subclass: #PPAndParser
  216. instanceVariableNames: ''
  217. category: 'Parser'!
  218. !PPAndParser methodsFor: 'parsing'!
  219. basicParse: aStream
  220. | element position |
  221. position := aStream position.
  222. element := self parser memoizedParse: aStream.
  223. aStream position: position.
  224. ^element
  225. !
  226. parse: aStream
  227. ^self basicParse: aStream
  228. ! !
  229. PPAndParser subclass: #PPNotParser
  230. instanceVariableNames: ''
  231. category: 'Parser'!
  232. !PPNotParser methodsFor: 'parsing'!
  233. parse: aStream
  234. | element |
  235. element := self basicParse: aStream.
  236. ^element isParseFailure
  237. ifTrue: [nil]
  238. ifFalse: [PPFailure reason: element at: aStream position]
  239. ! !
  240. PPDelegateParser subclass: #PPActionParser
  241. instanceVariableNames: 'block'
  242. category: 'Parser'!
  243. !PPActionParser class methodsFor: 'instance creation'!
  244. on: aParser block: aBlock
  245. ^self new
  246. parser: aParser;
  247. block: aBlock;
  248. yourself
  249. ! !
  250. !PPActionParser methodsFor: 'accessing'!
  251. block
  252. ^block
  253. !
  254. block: aBlock
  255. block := aBlock
  256. ! !
  257. !PPActionParser methodsFor: 'parsing'!
  258. parse: aStream
  259. | element |
  260. element := self parser memoizedParse: aStream.
  261. ^element isParseFailure
  262. ifFalse: [self block value: element]
  263. ifTrue: [element]
  264. ! !
  265. PPDelegateParser subclass: #PPFlattenParser
  266. instanceVariableNames: ''
  267. category: 'Parser'!
  268. !PPFlattenParser methodsFor: 'parsing'!
  269. parse: aStream
  270. | start element stop |
  271. start := aStream position.
  272. element := self parser memoizedParse: aStream.
  273. ^element isParseFailure
  274. ifTrue: [element]
  275. ifFalse: [aStream collection
  276. copyFrom: start + 1
  277. to: aStream position]
  278. ! !
  279. PPDelegateParser subclass: #PPSourceParser
  280. instanceVariableNames: ''
  281. category: 'Parser'!
  282. !PPSourceParser methodsFor: 'parsing'!
  283. parse: aStream
  284. | start element stop result |
  285. start := aStream position.
  286. element := self parser memoizedParse: aStream.
  287. ^element isParseFailure
  288. ifTrue: [element]
  289. ifFalse: [result := aStream collection copyFrom: start + 1 to: aStream position.
  290. Array with: element with: result].
  291. ! !
  292. PPDelegateParser subclass: #PPRepeatingParser
  293. instanceVariableNames: 'min'
  294. category: 'Parser'!
  295. !PPRepeatingParser class methodsFor: 'instance creation'!
  296. on: aParser min: aNumber
  297. ^self new
  298. parser: aParser;
  299. min: aNumber;
  300. yourself
  301. ! !
  302. !PPRepeatingParser methodsFor: 'accessing'!
  303. min
  304. ^min
  305. !
  306. min: aNumber
  307. min := aNumber
  308. ! !
  309. !PPRepeatingParser methodsFor: 'parsing'!
  310. parse: aStream
  311. | start element elements failure |
  312. start := aStream position.
  313. elements := Array new.
  314. [(elements size < self min) and: [failure isNil]] whileTrue: [
  315. element := self parser memoizedParse: aStream.
  316. element isParseFailure
  317. ifFalse: [elements addLast: element]
  318. ifTrue: [aStream position: start.
  319. failure := element]].
  320. ^failure ifNil: [
  321. [failure isNil] whileTrue: [
  322. element := self parser memoizedParse: aStream.
  323. element isParseFailure
  324. ifTrue: [failure := element]
  325. ifFalse: [elements addLast: element]].
  326. elements]
  327. ifNotNil: [failure].
  328. ! !
  329. Object subclass: #PPFailure
  330. instanceVariableNames: 'position reason'
  331. category: 'Parser'!
  332. !PPFailure class methodsFor: 'instance creation'!
  333. reason: aString at: anInteger
  334. ^self new
  335. reason: aString at: anInteger;
  336. yourself
  337. ! !
  338. !PPFailure methodsFor: 'accessing'!
  339. position
  340. ^position ifNil: [0]
  341. !
  342. position: aNumber
  343. position := aNumber
  344. !
  345. reason
  346. ^reason ifNil: ['']
  347. !
  348. reason: aString
  349. reason := aString
  350. !
  351. reason: aString at: anInteger
  352. self
  353. reason: aString;
  354. position: anInteger
  355. ! !
  356. !PPFailure methodsFor: 'testing'!
  357. isParseFailure
  358. ^true
  359. ! !
  360. Object subclass: #SmalltalkParser
  361. instanceVariableNames: ''
  362. category: 'Parser'!
  363. !SmalltalkParser class methodsFor: 'instance creation'!
  364. parse: aStream
  365. ^self new
  366. parse: aStream
  367. ! !
  368. !SmalltalkParser methodsFor: 'grammar'!
  369. parser
  370. | method expression separator comment ws identifier keyword className string symbol number literalArray variable reference classReference literal ret methodParser expressionParser keyword unarySelector binarySelector keywordPattern unaryPattern binaryPattern assignment temps blockParamList block expression expressions subexpression statements sequence operand unaryMessage unarySend unaryTail binaryMessage binarySend binaryTail keywordMessage keywordSend keywordPair cascade message jsStatement |
  371. separator := (String cr, String space, String lf, String tab) asChoiceParser.
  372. comment := ('"' asCharacterParser, ('"' asParser not, PPAnyParser new) star, '"' asCharacterParser) flatten.
  373. ws := (separator / comment) star.
  374. identifier := ('a-z' asCharacterParser, 'a-zA-Z0-9' asCharacterParser star) flatten.
  375. keyword := (identifier, ':' asParser) flatten.
  376. className := ('A-Z' asCharacterParser, 'a-zA-Z0-9' asCharacterParser star) flatten.
  377. string := '''' asParser, ('''''' asParser / ('''' asParser not, PPAnyParser new)) star flatten, '''' asParser
  378. ==> [:node | ValueNode new value: ((node at: 2) replace: '''''' with: '''')].
  379. symbol := '#' asParser, 'a-zA-Z0-9' asCharacterParser plus flatten
  380. ==> [:node | ValueNode new value: node second].
  381. number := ('0-9' asCharacterParser plus, ('.' asParser, '0-9' asCharacterParser plus) optional) flatten
  382. ==> [:node | ValueNode new value: node asNumber].
  383. literal := PPDelegateParser new.
  384. literalArray := '#(' asParser, (ws, literal, ws) star, ')' asParser
  385. ==> [:node | ValueNode new value: (Array withAll: (node second collect: [:each | each second value]))].
  386. variable := identifier ==> [:token | VariableNode new value: token].
  387. classReference := className ==> [:token | ClassReferenceNode new value: token].
  388. reference := variable / classReference.
  389. binarySelector := '+*/=><,@%~-' asCharacterParser plus flatten.
  390. unarySelector := identifier.
  391. keywordPattern := (ws, keyword, ws, identifier) plus
  392. ==> [:nodes | Array
  393. with: ((nodes collect: [:each | each at: 2]) join: '')
  394. with: (nodes collect: [:each | each at: 4])].
  395. binaryPattern := ws, binarySelector, ws, identifier
  396. ==> [:node | Array with: node second with: (Array with: node fourth)].
  397. unaryPattern := ws, unarySelector
  398. ==> [:node | Array with: node second with: Array new].
  399. expression := PPDelegateParser new.
  400. expressions := expression, ((ws, '.' asParser, ws, expression) ==> [:node | node fourth]) star
  401. ==> [:node || result |
  402. result := Array with: node first.
  403. node second do: [:each | result add: each].
  404. result].
  405. assignment := reference, ws, ':=' asParser, ws, expression
  406. ==> [:node | AssignmentNode new left: node first; right: (node at: 5)].
  407. ret := '^' asParser, ws, expression, ws, '.' asParser optional
  408. ==> [:node | ReturnNode new
  409. addNode: node third;
  410. yourself].
  411. temps := '|' asParser, (ws, identifier) star, ws, '|' asParser
  412. ==> [:node | node second collect: [:each | each second]].
  413. blockParamList := (':' asParser, identifier, ws) plus, '|' asParser
  414. ==> [:node | node first collect: [:each | each second]].
  415. subexpression := '(' asParser, ws, expression, ws, ')' asParser
  416. ==> [:node | node third].
  417. statements := (ret ==> [:node | Array with: node]) / (expressions, ws, '.' asParser, ws, ret ==> [:node | node first add: (node at: 5); yourself]) / (expressions , '.' asParser optional ==> [:node | node first]).
  418. sequence := temps optional, ws, statements optional, ws
  419. ==> [:node | SequenceNode new
  420. temps: node first;
  421. nodes: node third;
  422. yourself].
  423. block := '[' asParser, ws, blockParamList optional, ws, sequence optional, ws, ']' asParser
  424. ==> [:node |
  425. BlockNode new
  426. parameters: node third;
  427. addNode: (node at: 5) asBlockSequenceNode].
  428. operand := literal / reference / subexpression.
  429. literal parser: number / string / literalArray / symbol / block.
  430. unaryMessage := ws, unarySelector, ':' asParser not
  431. ==> [:node | SendNode new selector: node second].
  432. unaryTail := PPDelegateParser new.
  433. unaryTail parser: (unaryMessage, unaryTail optional
  434. ==> [:node |
  435. node second
  436. ifNil: [node first]
  437. ifNotNil: [node second valueForReceiver: node first]]).
  438. unarySend := operand, unaryTail optional
  439. ==> [:node |
  440. node second
  441. ifNil: [node first]
  442. ifNotNil: [node second valueForReceiver: node first]].
  443. binaryMessage := ws, binarySelector, ws, (unarySend / operand)
  444. ==> [:node |
  445. SendNode new
  446. selector: node second;
  447. arguments: (Array with: node fourth)].
  448. binaryTail := PPDelegateParser new.
  449. binaryTail parser: (binaryMessage, binaryTail optional
  450. ==> [:node |
  451. node second
  452. ifNil: [node first]
  453. ifNotNil: [ node second valueForReceiver: node first]]).
  454. binarySend := unarySend, binaryTail optional
  455. ==> [:node |
  456. node second
  457. ifNil: [node first]
  458. ifNotNil: [node second valueForReceiver: node first]].
  459. keywordPair := keyword, ws, binarySend.
  460. keywordMessage := (ws, keywordPair) plus
  461. ==> [:nodes |
  462. SendNode new
  463. selector: ((nodes collect: [:each | each second first]) join: '');
  464. arguments: (nodes collect: [:each | each second third])].
  465. keywordSend := binarySend, keywordMessage
  466. ==> [:node |
  467. node second valueForReceiver: node first].
  468. message := binaryMessage / unaryMessage / keywordMessage.
  469. cascade := (keywordSend / binarySend), (ws, ';' asParser, message) plus
  470. ==> [:node |
  471. node first cascadeNodeWithMessages:
  472. (node second collect: [:each | each third])].
  473. jsStatement := '{' asParser, ws, string, ws, '}' asParser
  474. ==> [:node | JSStatementNode new
  475. source: node third;
  476. yourself].
  477. expression parser: assignment / cascade / keywordSend / binarySend / jsStatement.
  478. method := (ws, (keywordPattern / binaryPattern / unaryPattern), ws, sequence optional, ws) withSource
  479. ==> [:node |
  480. MethodNode new
  481. selector: node first second first;
  482. arguments: node first second second;
  483. addNode: node first fourth;
  484. source: node second;
  485. yourself].
  486. ^method, PPEOFParser new ==> [:node | node first]
  487. ! !
  488. !SmalltalkParser methodsFor: 'parsing'!
  489. parse: aStream
  490. ^self parser parse: aStream
  491. ! !
  492. Object subclass: #Chunk
  493. instanceVariableNames: 'contents'
  494. category: 'Parser'!
  495. !Chunk methodsFor: 'accessing'!
  496. contents
  497. ^contents ifNil: ['']
  498. !
  499. contents: aString
  500. contents := aString
  501. ! !
  502. !Chunk methodsFor: 'testing'!
  503. isEmptyChunk
  504. ^false
  505. !
  506. isInstructionChunk
  507. ^false
  508. ! !
  509. Chunk subclass: #InstructionChunk
  510. instanceVariableNames: ''
  511. category: 'Parser'!
  512. !InstructionChunk methodsFor: 'testing'!
  513. isInstructionChunk
  514. ^true
  515. ! !
  516. Chunk subclass: #EmptyChunk
  517. instanceVariableNames: ''
  518. category: 'Parser'!
  519. !EmptyChunk methodsFor: 'testing'!
  520. isEmptyChunk
  521. ^true
  522. ! !
  523. Object subclass: #ChunkParser
  524. instanceVariableNames: 'parser separator eof ws chunk emptyChunk instructionChunk'
  525. category: 'Parser'!
  526. !ChunkParser methodsFor: 'accessing'!
  527. chunk
  528. ^chunk ifNil: [chunk := self ws, ('!!!!' asParser / ('!!' asParser not, PPAnyParser new)) plus flatten, '!!' asParser ==> [:node | Chunk new contents: (node second replace: '!!!!' with: '!!')]]
  529. !
  530. emptyChunk
  531. ^emptyChunk ifNil: [emptyChunk := self separator plus, '!!' asParser, self ws ==> [:node | EmptyChunk new]]
  532. !
  533. eof
  534. ^eof ifNil: [eof := self ws, PPEOFParser new ==> [:node | nil]]
  535. !
  536. parser
  537. ^parser ifNil: [
  538. parser := self instructionChunk / self emptyChunk / self chunk / self eof]
  539. !
  540. separator
  541. ^separator ifNil: [separator := (String cr, String space, String lf, String tab) asChoiceParser]
  542. !
  543. ws
  544. ^ws ifNil: [ws := self separator star]
  545. ! !
  546. !ChunkParser methodsFor: nil!
  547. instructionChunk
  548. ^instructionChunk ifNil: [
  549. instructionChunk := self ws, '!!' asParser, self chunk
  550. ==> [:node | InstructionChunk new contents: node last contents]]
  551. ! !
  552. Object subclass: #Importer
  553. instanceVariableNames: 'chunkParser'
  554. category: 'Parser'!
  555. !Importer methodsFor: 'accessing'!
  556. chunkParser
  557. ^chunkParser ifNil: [chunkParser := ChunkParser new parser]
  558. ! !
  559. !Importer methodsFor: 'fileIn'!
  560. import: aStream
  561. aStream atEnd ifFalse: [
  562. | nextChunk |
  563. nextChunk := self chunkParser parse: aStream.
  564. nextChunk ifNotNil: [
  565. nextChunk isInstructionChunk
  566. ifTrue: [(Compiler new loadExpression: nextChunk contents)
  567. scanFrom: aStream]
  568. ifFalse: [Compiler new loadExpression: nextChunk contents].
  569. self import: aStream]]
  570. ! !
  571. Object subclass: #Exporter
  572. instanceVariableNames: ''
  573. category: 'Parser'!
  574. !Exporter methodsFor: 'fileout'!
  575. exportCategory: aString
  576. | stream |
  577. stream := '' writeStream.
  578. (Smalltalk current classes
  579. select: [:each | each category = aString])
  580. do: [:each | stream nextPutAll: (self export: each)].
  581. ^stream contents
  582. ! !
  583. !Exporter methodsFor: 'fileOut'!
  584. export: aClass
  585. | stream |
  586. stream := '' writeStream.
  587. self exportDefinitionOf: aClass on: stream.
  588. stream nextPutAll: String cr.
  589. self exportMethodsOf: aClass on: stream.
  590. stream nextPutAll: String cr.
  591. self exportMetaDefinitionOf: aClass on: stream.
  592. self exportMethodsOf: aClass class on: stream.
  593. stream nextPutAll: String cr.
  594. ^stream contents
  595. ! !
  596. !Exporter methodsFor: 'private'!
  597. classNameFor: aClass
  598. ^aClass isMetaclass
  599. ifTrue: [aClass instanceClass name, '.klass']
  600. ifFalse: [
  601. aClass isNil
  602. ifTrue: ['nil']
  603. ifFalse: [aClass name]]
  604. !
  605. exportDefinitionOf: aClass on: aStream
  606. aStream
  607. nextPutAll: 'smalltalk.addClass(';
  608. nextPutAll: '''', (self classNameFor: aClass), ''', ';
  609. nextPutAll: 'smalltalk.', (self classNameFor: aClass superclass);
  610. nextPutAll: ', ['.
  611. aClass instVarNames
  612. do: [:each | aStream nextPutAll: '''', each, '''']
  613. separatedBy: [aStream nextPutAll: ', '].
  614. aStream
  615. nextPutAll: '], ''';
  616. nextPutAll: aClass category, '''';
  617. nextPutAll: ');'.
  618. aClass comment notEmpty ifTrue: [
  619. aStream
  620. nextPutAll: String cr;
  621. nextPutAll: 'smalltalk.';
  622. nextPutAll: (self classNameFor: aClass);
  623. nextPutAll: '.comment=';
  624. nextPutAll: 'unescape(''', aClass comment escaped, ''')']
  625. !
  626. exportMetaDefinitionOf: aClass on: aStream
  627. aClass class instVarNames isEmpty ifFalse: [
  628. aStream
  629. nextPutAll: 'smalltalk.', (self classNameFor: aClass class);
  630. nextPutAll: '.iVarNames = ['.
  631. aClass class instVarNames
  632. do: [:each | aStream nextPutAll: '''', each, '''']
  633. separatedBy: [aStream nextPutAll: ','].
  634. aStream nextPutAll: '];', String cr]
  635. !
  636. exportMethodsOf: aClass on: aStream
  637. aClass methodDictionary keysAndValuesDo: [:key :value |
  638. aStream
  639. nextPutAll: 'smalltalk.addMethod(', String cr;
  640. nextPutAll: '''', value selector asSelector, ''',', String cr;
  641. nextPutAll: 'smalltalk.method({', String cr;
  642. nextPutAll: 'selector: ''', value selector, ''',', String cr;
  643. nextPutAll: 'category: ''', value category, ''',', String cr;
  644. nextPutAll: 'fn: ', value fn compiledSource, ',', String cr;
  645. nextPutAll: 'source: unescape(''', value source escaped, ''')';
  646. nextPutAll: '}),', String cr;
  647. nextPutAll: 'smalltalk.', (self classNameFor: aClass);
  648. nextPutAll: ');', String cr, String cr]
  649. ! !