Parser.st 22 KB

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