1
0

Kernel-Collections.st 34 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863
  1. Smalltalk current createPackage: 'Kernel-Collections'!
  2. Object subclass: #Association
  3. instanceVariableNames: 'key value'
  4. package: 'Kernel-Collections'!
  5. !Association commentStamp!
  6. I represent a pair of associated objects, a key and a value. My instances can serve as entries in a dictionary.
  7. Instances can be created with the class-side method `#key:value:`!
  8. !Association methodsFor: 'accessing'!
  9. key
  10. ^key
  11. !
  12. key: aKey
  13. key := aKey
  14. !
  15. value
  16. ^value
  17. !
  18. value: aValue
  19. value := aValue
  20. ! !
  21. !Association methodsFor: 'comparing'!
  22. = anAssociation
  23. ^self class = anAssociation class and: [
  24. self key = anAssociation key and: [
  25. self value = anAssociation value]]
  26. ! !
  27. !Association methodsFor: 'printing'!
  28. printOn: aStream
  29. self key printOn: aStream.
  30. aStream nextPutAll: ' -> '.
  31. self value printOn: aStream
  32. ! !
  33. !Association class methodsFor: 'instance creation'!
  34. key: aKey value: aValue
  35. ^self new
  36. key: aKey;
  37. value: aValue;
  38. yourself
  39. ! !
  40. Object subclass: #Collection
  41. instanceVariableNames: ''
  42. package: 'Kernel-Collections'!
  43. !Collection commentStamp!
  44. I am the abstract superclass of all classes that represent a group of elements.
  45. I provide a set of useful methods to the Collection hierarchy such as enumerating and converting methods.!
  46. !Collection methodsFor: 'accessing'!
  47. occurrencesOf: anObject
  48. "Answer how many of the receiver's elements are equal to anObject."
  49. | tally |
  50. tally := 0.
  51. self do: [:each | anObject = each ifTrue: [tally := tally + 1]].
  52. ^tally
  53. !
  54. size
  55. self subclassResponsibility
  56. ! !
  57. !Collection methodsFor: 'adding/removing'!
  58. add: anObject
  59. self subclassResponsibility
  60. !
  61. addAll: aCollection
  62. aCollection do: [:each |
  63. self add: each].
  64. ^aCollection
  65. !
  66. remove: anObject
  67. ^self remove: anObject ifAbsent: [self errorNotFound]
  68. !
  69. remove: anObject ifAbsent: aBlock
  70. self subclassResponsibility
  71. ! !
  72. !Collection methodsFor: 'converting'!
  73. asArray
  74. ^Array withAll: self
  75. !
  76. asJSON
  77. ^self asArray collect: [:each | each asJSON]
  78. !
  79. asOrderedCollection
  80. ^self asArray
  81. !
  82. asSet
  83. ^Set withAll: self
  84. ! !
  85. !Collection methodsFor: 'copying'!
  86. , aCollection
  87. ^self copy
  88. addAll: aCollection;
  89. yourself
  90. !
  91. copyWith: anObject
  92. ^self copy add: anObject; yourself
  93. !
  94. copyWithAll: aCollection
  95. ^self copy addAll: aCollection; yourself
  96. !
  97. copyWithoutAll: aCollection
  98. "Answer a copy of the receiver that does not contain any elements
  99. equal to those in aCollection."
  100. ^ self reject: [:each | aCollection includes: each]
  101. ! !
  102. !Collection methodsFor: 'enumerating'!
  103. anySatisfy: aBlock
  104. "Evaluate aBlock with the elements of the receiver.
  105. If aBlock returns true for any element return true.
  106. Otherwise return false."
  107. self do: [ :each | (aBlock value: each) ifTrue: [ ^ true ] ].
  108. ^ false
  109. !
  110. collect: aBlock
  111. | stream |
  112. stream := self class new writeStream.
  113. self do: [ :each |
  114. stream nextPut: (aBlock value: each) ].
  115. ^stream contents
  116. !
  117. contains: aBlock
  118. ^ self anySatisfy: aBlock
  119. !
  120. detect: aBlock
  121. ^self detect: aBlock ifNone: [self errorNotFound]
  122. !
  123. detect: aBlock ifNone: anotherBlock
  124. self subclassResponsibility
  125. !
  126. do: aBlock
  127. self subclassResponsibility
  128. !
  129. do: aBlock separatedBy: anotherBlock
  130. | actionBeforeElement |
  131. actionBeforeElement := [actionBeforeElement := anotherBlock].
  132. self do: [:each |
  133. actionBeforeElement value.
  134. aBlock value: each]
  135. !
  136. inject: anObject into: aBlock
  137. | result |
  138. result := anObject.
  139. self do: [:each |
  140. result := aBlock value: result value: each].
  141. ^result
  142. !
  143. intersection: aCollection
  144. "Answer the set theoretic intersection of two collections."
  145. | set outputSet |
  146. set := self asSet.
  147. outputSet := Set new.
  148. aCollection do: [ :each |
  149. ((set includes: each) and: [(outputSet includes: each) not])
  150. ifTrue: [
  151. outputSet add: each]].
  152. ^ self class withAll: outputSet asArray
  153. !
  154. reject: aBlock
  155. ^self select: [:each | (aBlock value: each) = false]
  156. !
  157. select: aBlock
  158. | stream |
  159. stream := self class new writeStream.
  160. self do: [:each |
  161. (aBlock value: each) ifTrue: [
  162. stream nextPut: each]].
  163. ^stream contents
  164. ! !
  165. !Collection methodsFor: 'error handling'!
  166. errorNotFound
  167. self error: 'Object is not in the collection'
  168. ! !
  169. !Collection methodsFor: 'streaming'!
  170. putOn: aStream
  171. self do: [ :each | each putOn: aStream ]
  172. ! !
  173. !Collection methodsFor: 'testing'!
  174. ifEmpty: aBlock
  175. "Evaluate the given block with the receiver as argument, answering its value if the receiver is empty, otherwise answer the receiver. Note that the fact that this method returns its argument in case the receiver is not empty allows one to write expressions like the following ones: self classifyMethodAs:
  176. (myProtocol ifEmpty: ['As yet unclassified'])"
  177. ^ self isEmpty
  178. ifTrue: [ aBlock value ]
  179. ifFalse: [ self ]
  180. !
  181. ifNotEmpty: aBlock
  182. self notEmpty ifTrue: aBlock.
  183. !
  184. includes: anObject
  185. | sentinel |
  186. sentinel := Object new.
  187. ^(self detect: [ :each | each = anObject] ifNone: [ sentinel ]) ~= sentinel
  188. !
  189. isEmpty
  190. ^self size = 0
  191. !
  192. notEmpty
  193. ^self isEmpty not
  194. ! !
  195. !Collection class methodsFor: 'helios'!
  196. heliosClass
  197. ^ 'collection'
  198. ! !
  199. !Collection class methodsFor: 'instance creation'!
  200. new: anInteger
  201. ^self new
  202. !
  203. with: anObject
  204. ^self new
  205. add: anObject;
  206. yourself
  207. !
  208. with: anObject with: anotherObject
  209. ^self new
  210. add: anObject;
  211. add: anotherObject;
  212. yourself
  213. !
  214. with: firstObject with: secondObject with: thirdObject
  215. ^self new
  216. add: firstObject;
  217. add: secondObject;
  218. add: thirdObject;
  219. yourself
  220. !
  221. withAll: aCollection
  222. ^self new
  223. addAll: aCollection;
  224. yourself
  225. ! !
  226. Collection subclass: #IndexableCollection
  227. instanceVariableNames: ''
  228. package: 'Kernel-Collections'!
  229. !IndexableCollection commentStamp!
  230. I am a key-value store collection, that is,
  231. I store values under indexes.
  232. As a rule of thumb, if a collection has `#at:` and `#at:put:`,
  233. it is an IndexableCollection.!
  234. !IndexableCollection methodsFor: 'accessing'!
  235. at: anIndex
  236. "Lookup the given index in the receiver.
  237. If it is present, answer the value stored at anIndex.
  238. Otherwise, raise an error."
  239. ^self at: anIndex ifAbsent: [ self errorNotFound ]
  240. !
  241. at: anIndex ifAbsent: aBlock
  242. "Lookup the given index in the receiver.
  243. If it is present, answer the value stored at anIndex.
  244. Otherwise, answer the value of aBlock."
  245. self subclassReponsibility
  246. !
  247. at: anIndex ifPresent: aBlock
  248. "Lookup the given index in the receiver.
  249. If it is present, answer the value of evaluating aBlock with the value stored at anIndex.
  250. Otherwise, answer nil."
  251. ^self at: anIndex ifPresent: aBlock ifAbsent: [ nil ]
  252. !
  253. at: anIndex ifPresent: aBlock ifAbsent: anotherBlock
  254. "Lookup the given index in the receiver.
  255. If it is present, answer the value of evaluating aBlock with the value stored at anIndex.
  256. Otherwise, answer the value of anotherBlock."
  257. self subclassResponsibility
  258. !
  259. at: anIndex put: anObject
  260. "Store anObject under the given index in the receiver."
  261. self subclassReponsibility
  262. !
  263. indexOf: anObject
  264. "Lookup index at which anObject is stored in the receiver.
  265. If not present, raise an error."
  266. ^self indexOf: anObject ifAbsent: [ self errorNotFound ]
  267. !
  268. indexOf: anObject ifAbsent: aBlock
  269. "Lookup index at which anObject is stored in the receiver.
  270. If not present, return value of executing aBlock."
  271. self subclassResponsibility
  272. ! !
  273. !IndexableCollection methodsFor: 'enumarating'!
  274. with: anotherCollection do: aBlock
  275. "Calls aBlock with every value from self
  276. and with indetically-indexed value from anotherCollection"
  277. self withIndexDo: [ :each :index |
  278. aBlock value: each value: (anotherCollection at: index) ]
  279. !
  280. withIndexDo: aBlock
  281. "Calls aBlock with every value from self
  282. and with its index as the second argument"
  283. self subclassReponsibility
  284. ! !
  285. IndexableCollection subclass: #HashedCollection
  286. instanceVariableNames: ''
  287. package: 'Kernel-Collections'!
  288. !HashedCollection commentStamp!
  289. I am a traditional JavaScript object, or a Smalltalk `Dictionary`.
  290. Unlike a `Dictionary`, I can only have strings as keys.!
  291. !HashedCollection methodsFor: 'accessing'!
  292. associations
  293. | associations |
  294. associations := #().
  295. self associationsDo: [:each | associations add: each].
  296. ^associations
  297. !
  298. at: aKey ifAbsent: aBlock
  299. ^(self includesKey: aKey)
  300. ifTrue: [self basicAt: aKey]
  301. ifFalse: aBlock
  302. !
  303. at: aKey ifAbsentPut: aBlock
  304. ^self at: aKey ifAbsent: [
  305. self at: aKey put: aBlock value]
  306. !
  307. at: aKey ifPresent: aBlock ifAbsent: anotherBlock
  308. "Lookup the given key in the receiver.
  309. If it is present, answer the value of evaluating the oneArgBlock with the value associated with the key,
  310. otherwise answer the value of absentBlock."
  311. ^(self includesKey: aKey)
  312. ifTrue: [ aBlock value: (self at: aKey) ]
  313. ifFalse: anotherBlock
  314. !
  315. at: aKey put: aValue
  316. ^self basicAt: aKey put: aValue
  317. !
  318. indexOf: anObject ifAbsent: aBlock
  319. ^ self keys detect: [ :each | (self at: each) = anObject ] ifNone: aBlock
  320. !
  321. keys
  322. <
  323. if ('function'===typeof Object.keys) return Object.keys(self);
  324. var keys = [];
  325. for(var i in self) {
  326. if(self.hasOwnProperty(i)) {
  327. keys.push(i);
  328. }
  329. };
  330. return keys;
  331. >
  332. !
  333. size
  334. ^self keys size
  335. !
  336. values
  337. ^self keys collect: [:each | self at: each]
  338. ! !
  339. !HashedCollection methodsFor: 'adding/removing'!
  340. add: anAssociation
  341. self at: anAssociation key put: anAssociation value
  342. !
  343. addAll: aHashedCollection
  344. super addAll: aHashedCollection associations.
  345. ^aHashedCollection
  346. !
  347. remove: aKey ifAbsent: aBlock
  348. ^self removeKey: aKey ifAbsent: aBlock
  349. !
  350. removeKey: aKey
  351. ^self remove: aKey
  352. !
  353. removeKey: aKey ifAbsent: aBlock
  354. ^(self includesKey: aKey)
  355. ifFalse: [aBlock value]
  356. ifTrue: [self basicDelete: aKey]
  357. ! !
  358. !HashedCollection methodsFor: 'comparing'!
  359. = aHashedCollection
  360. self class = aHashedCollection class ifFalse: [^false].
  361. self size = aHashedCollection size ifFalse: [^false].
  362. ^self associations = aHashedCollection associations
  363. ! !
  364. !HashedCollection methodsFor: 'converting'!
  365. asDictionary
  366. ^Dictionary fromPairs: self associations
  367. !
  368. asJSON
  369. | c |
  370. c := self class new.
  371. self keysAndValuesDo: [:key :value |
  372. c at: key put: value asJSON].
  373. ^c
  374. ! !
  375. !HashedCollection methodsFor: 'copying'!
  376. , aCollection
  377. self shouldNotImplement
  378. !
  379. deepCopy
  380. | copy |
  381. copy := self class new.
  382. self keysAndValuesDo: [:key :value |
  383. copy at: key put: value deepCopy].
  384. ^copy
  385. !
  386. shallowCopy
  387. | copy |
  388. copy := self class new.
  389. self keysAndValuesDo: [:key :value |
  390. copy at: key put: value].
  391. ^copy
  392. ! !
  393. !HashedCollection methodsFor: 'enumerating'!
  394. associationsDo: aBlock
  395. self keysAndValuesDo: [:key :value |
  396. aBlock value: (Association key: key value: value)]
  397. !
  398. collect: aBlock
  399. | newDict |
  400. newDict := self class new.
  401. self keysAndValuesDo: [:key :value |
  402. newDict at: key put: (aBlock value: value)].
  403. ^newDict
  404. !
  405. detect: aBlock ifNone: anotherBlock
  406. ^self values detect: aBlock ifNone: anotherBlock
  407. !
  408. do: aBlock
  409. self valuesDo: aBlock
  410. !
  411. includes: anObject
  412. ^self values includes: anObject
  413. !
  414. keysAndValuesDo: aBlock
  415. self keysDo: [:each |
  416. aBlock value: each value: (self at: each)]
  417. !
  418. keysDo: aBlock
  419. self keys do: aBlock
  420. !
  421. select: aBlock
  422. | newDict |
  423. newDict := self class new.
  424. self keysAndValuesDo: [:key :value |
  425. (aBlock value: value) ifTrue: [newDict at: key put: value]].
  426. ^newDict
  427. !
  428. valuesDo: aBlock
  429. self keysAndValuesDo: [ :key :value | aBlock value: value ]
  430. !
  431. withIndexDo: aBlock
  432. self keysAndValuesDo: [ :key :value | aBlock value: value value: key ]
  433. ! !
  434. !HashedCollection methodsFor: 'printing'!
  435. printOn: aStream
  436. super printOn: aStream.
  437. aStream nextPutAll: ' ('.
  438. self associations
  439. do: [:each | each printOn: aStream ]
  440. separatedBy: [ aStream nextPutAll: ' , ' ].
  441. aStream nextPutAll: ')'
  442. ! !
  443. !HashedCollection methodsFor: 'testing'!
  444. includesKey: aKey
  445. <return self.hasOwnProperty(aKey)>
  446. ! !
  447. !HashedCollection class methodsFor: 'instance creation'!
  448. fromPairs: aCollection
  449. | dict |
  450. dict := self new.
  451. aCollection do: [:each | dict add: each].
  452. ^dict
  453. ! !
  454. HashedCollection subclass: #Dictionary
  455. instanceVariableNames: 'keys values'
  456. package: 'Kernel-Collections'!
  457. !Dictionary commentStamp!
  458. I represent a set of elements that can be viewed from one of two perspectives: a set of associations,
  459. or a container of values that are externally named where the name can be any object that responds to `=`.
  460. The external name is referred to as the key.!
  461. !Dictionary methodsFor: 'accessing'!
  462. at: aKey ifAbsent: aBlock
  463. <
  464. var index = self._positionOfKey_(aKey);
  465. return index >>=0 ? self['@values'][index] : aBlock();
  466. >
  467. !
  468. at: aKey put: aValue
  469. <
  470. var index = self._positionOfKey_(aKey);
  471. if(index === -1) {
  472. var keys = self['@keys'];
  473. index = keys.length;
  474. keys.push(aKey);
  475. }
  476. return self['@values'][index] = aValue;
  477. >
  478. !
  479. indexOf: anObject ifAbsent: aBlock
  480. | index |
  481. index := values indexOf: anObject ifAbsent: [0].
  482. ^ index = 0 ifTrue: [ aBlock value ] ifFalse: [ keys at: index ]
  483. !
  484. keys
  485. ^keys copy
  486. !
  487. values
  488. ^values copy
  489. ! !
  490. !Dictionary methodsFor: 'adding/removing'!
  491. removeKey: aKey ifAbsent: aBlock
  492. <
  493. var index = self._positionOfKey_(aKey);
  494. if(index === -1) {
  495. return aBlock()
  496. } else {
  497. var keys = self['@keys'], values = self['@values'];
  498. var value = values[index], l = keys.length;
  499. keys[index] = keys[l-1];
  500. keys.pop();
  501. values[index] = values[l-1];
  502. values.pop();
  503. return value;
  504. }
  505. >
  506. ! !
  507. !Dictionary methodsFor: 'converting'!
  508. asHashedCollection
  509. ^HashedCollection fromPairs: self associations
  510. !
  511. asJSON
  512. ^self asHashedCollection asJSON
  513. ! !
  514. !Dictionary methodsFor: 'enumerating'!
  515. keysAndValuesDo: aBlock
  516. ^keys with: values do: aBlock
  517. !
  518. keysDo: aBlock
  519. ^keys do: aBlock
  520. !
  521. valuesDo: aBlock
  522. ^values do: aBlock
  523. ! !
  524. !Dictionary methodsFor: 'initialization'!
  525. initialize
  526. super initialize.
  527. keys := #().
  528. values := #()
  529. ! !
  530. !Dictionary methodsFor: 'private'!
  531. positionOfKey: anObject
  532. <
  533. var keys = self['@keys'];
  534. for(var i=0;i<keys.length;i++){
  535. if(keys[i].__eq(anObject)) { return i;}
  536. }
  537. return -1;
  538. >
  539. ! !
  540. !Dictionary methodsFor: 'testing'!
  541. includesKey: aKey
  542. < return self._positionOfKey_(aKey) >>= 0; >
  543. ! !
  544. IndexableCollection subclass: #SequenceableCollection
  545. instanceVariableNames: ''
  546. package: 'Kernel-Collections'!
  547. !SequenceableCollection commentStamp!
  548. I am an IndexableCollection
  549. with numeric indexes starting with 1.!
  550. !SequenceableCollection methodsFor: 'accessing'!
  551. allButFirst
  552. ^self copyFrom: 2 to: self size
  553. !
  554. allButLast
  555. ^self copyFrom: 1 to: self size - 1
  556. !
  557. atRandom
  558. ^ self at: self size atRandom
  559. !
  560. first
  561. ^self at: 1
  562. !
  563. first: n
  564. "Answer the first n elements of the receiver.
  565. Raise an error if there are not enough elements."
  566. ^ self copyFrom: 1 to: n
  567. !
  568. fourth
  569. ^self at: 4
  570. !
  571. indexOf: anObject ifAbsent: aBlock
  572. <
  573. for(var i=0;i<self.length;i++) {
  574. if(self[i].__eq(anObject)) {return i+1}
  575. };
  576. return aBlock();
  577. >
  578. !
  579. indexOf: anObject startingAt: start
  580. "Answer the index of the first occurence of anElement after start
  581. within the receiver. If the receiver does not contain anElement,
  582. answer 0."
  583. ^self indexOf: anObject startingAt: start ifAbsent: [0]
  584. !
  585. indexOf: anObject startingAt: start ifAbsent: aBlock
  586. <
  587. for(var i=start-1;i<self.length;i++){
  588. if(self[i].__eq(anObject)) {return i+1}
  589. }
  590. return aBlock();
  591. >
  592. !
  593. last
  594. ^self at: self size
  595. !
  596. second
  597. ^self at: 2
  598. !
  599. third
  600. ^self at: 3
  601. ! !
  602. !SequenceableCollection methodsFor: 'adding'!
  603. addLast: anObject
  604. self add: anObject
  605. !
  606. removeLast
  607. self remove: self last
  608. ! !
  609. !SequenceableCollection methodsFor: 'comparing'!
  610. = aCollection
  611. (self class = aCollection class and: [
  612. self size = aCollection size]) ifFalse: [^false].
  613. self withIndexDo: [:each :i |
  614. (aCollection at: i) = each ifFalse: [^false]].
  615. ^true
  616. ! !
  617. !SequenceableCollection methodsFor: 'converting'!
  618. reversed
  619. self subclassResponsibility
  620. ! !
  621. !SequenceableCollection methodsFor: 'copying'!
  622. copyFrom: anIndex to: anotherIndex
  623. | range newCollection |
  624. range := anIndex to: anotherIndex.
  625. newCollection := self class new: range size.
  626. range withIndexDo: [:each :i |
  627. newCollection at: i put: (self at: each)].
  628. ^newCollection
  629. !
  630. deepCopy
  631. | newCollection |
  632. newCollection := self class new: self size.
  633. self withIndexDo: [:each :index |
  634. newCollection at: index put: each deepCopy].
  635. ^newCollection
  636. !
  637. shallowCopy
  638. | newCollection |
  639. newCollection := self class new: self size.
  640. self withIndexDo: [ :each :index |
  641. newCollection at: index put: each].
  642. ^newCollection
  643. ! !
  644. !SequenceableCollection methodsFor: 'enumerating'!
  645. detect: aBlock ifNone: anotherBlock
  646. <
  647. for(var i = 0; i < self.length; i++)
  648. if(aBlock(self[i]))
  649. return self[i];
  650. return anotherBlock();
  651. >
  652. !
  653. do: aBlock
  654. <for(var i=0;i<self.length;i++){aBlock(self[i]);}>
  655. !
  656. with: anotherCollection do: aBlock
  657. <for(var i=0;i<self.length;i++){aBlock(self[i], anotherCollection[i]);}>
  658. !
  659. withIndexDo: aBlock
  660. <for(var i=0;i<self.length;i++){aBlock(self[i], i+1);}>
  661. ! !
  662. !SequenceableCollection methodsFor: 'streaming'!
  663. newStream
  664. ^self streamClass on: self
  665. !
  666. readStream
  667. "For Pharo compatibility"
  668. ^self stream
  669. !
  670. stream
  671. ^self newStream
  672. !
  673. streamClass
  674. ^self class streamClass
  675. !
  676. writeStream
  677. "For Pharo compatibility"
  678. ^self stream
  679. ! !
  680. !SequenceableCollection methodsFor: 'testing'!
  681. includes: anObject
  682. ^(self indexOf: anObject ifAbsent: [nil]) notNil
  683. ! !
  684. !SequenceableCollection class methodsFor: 'accessing'!
  685. streamClass
  686. ^Stream
  687. ! !
  688. !SequenceableCollection class methodsFor: 'streaming'!
  689. streamContents: aBlock
  690. | stream |
  691. stream := (self streamClass on: self new).
  692. aBlock value: stream.
  693. ^ stream contents
  694. ! !
  695. SequenceableCollection subclass: #Array
  696. instanceVariableNames: ''
  697. package: 'Kernel-Collections'!
  698. !Array commentStamp!
  699. I represent a collection of objects ordered by the collector. The size of arrays is dynamic.
  700. I am directly mapped to JavaScript Number.
  701. *Note* In Amber, `OrderedCollection` is an alias for `Array`.!
  702. !Array methodsFor: 'accessing'!
  703. at: anIndex ifAbsent: aBlock
  704. <
  705. if((anIndex < 1) || (self.length < anIndex)) {return aBlock()};
  706. return self[anIndex - 1];
  707. >
  708. !
  709. at: anIndex ifPresent: aBlock ifAbsent: anotherBlock
  710. <return anIndex < 1 || self.length < anIndex ? anotherBlock._value() : aBlock._value_(self[anIndex - 1]);>
  711. !
  712. at: anIndex put: anObject
  713. <return self[anIndex - 1] = anObject>
  714. !
  715. size
  716. <return self.length>
  717. ! !
  718. !Array methodsFor: 'adding/removing'!
  719. add: anObject
  720. <self.push(anObject); return anObject;>
  721. !
  722. remove: anObject ifAbsent: aBlock
  723. <
  724. for(var i=0;i<self.length;i++) {
  725. if(self[i] == anObject) {
  726. self.splice(i,1);
  727. return self;
  728. }
  729. };
  730. aBlock._value();
  731. >
  732. !
  733. removeFrom: aNumber to: anotherNumber
  734. <self.splice(aNumber - 1,anotherNumber - 1)>
  735. ! !
  736. !Array methodsFor: 'converting'!
  737. asJavascript
  738. ^'[', ((self collect: [:each | each asJavascript]) join: ', '), ']'
  739. !
  740. reversed
  741. <return self._copy().reverse()>
  742. ! !
  743. !Array methodsFor: 'enumerating'!
  744. join: aString
  745. <return self.join(aString)>
  746. !
  747. sort
  748. ^self basicPerform: 'sort'
  749. !
  750. sort: aBlock
  751. <
  752. return self.sort(function(a, b) {
  753. if(aBlock(a,b)) {return -1} else {return 1}
  754. })
  755. >
  756. !
  757. sorted
  758. ^self copy sort
  759. !
  760. sorted: aBlock
  761. ^self copy sort: aBlock
  762. ! !
  763. !Array methodsFor: 'printing'!
  764. printOn: aStream
  765. super printOn: aStream.
  766. aStream nextPutAll: ' ('.
  767. self
  768. do: [ :each | each printOn: aStream ]
  769. separatedBy: [ aStream nextPutAll: ' ' ].
  770. aStream nextPutAll: ')'
  771. ! !
  772. !Array class methodsFor: 'instance creation'!
  773. new: anInteger
  774. <return new Array(anInteger)>
  775. !
  776. with: anObject
  777. ^(self new: 1)
  778. at: 1 put: anObject;
  779. yourself
  780. !
  781. with: anObject with: anObject2
  782. ^(self new: 2)
  783. at: 1 put: anObject;
  784. at: 2 put: anObject2;
  785. yourself
  786. !
  787. with: anObject with: anObject2 with: anObject3
  788. ^(self new: 3)
  789. at: 1 put: anObject;
  790. at: 2 put: anObject2;
  791. at: 3 put: anObject3;
  792. yourself
  793. !
  794. withAll: aCollection
  795. | instance index |
  796. index := 1.
  797. instance := self new: aCollection size.
  798. aCollection do: [:each |
  799. instance at: index put: each.
  800. index := index + 1].
  801. ^instance
  802. ! !
  803. SequenceableCollection subclass: #CharacterArray
  804. instanceVariableNames: ''
  805. package: 'Kernel-Collections'!
  806. !CharacterArray commentStamp!
  807. I am the abstract superclass of string-like collections.!
  808. !CharacterArray methodsFor: 'accessing'!
  809. at: anIndex put: anObject
  810. self errorReadOnly
  811. ! !
  812. !CharacterArray methodsFor: 'adding'!
  813. add: anObject
  814. self errorReadOnly
  815. !
  816. remove: anObject
  817. self errorReadOnly
  818. ! !
  819. !CharacterArray methodsFor: 'converting'!
  820. asLowercase
  821. ^self class fromString: self asString asLowercase
  822. !
  823. asNumber
  824. ^self asString asNumber
  825. !
  826. asString
  827. ^self subclassResponsibility
  828. !
  829. asSymbol
  830. ^self asString
  831. !
  832. asUppercase
  833. ^self class fromString: self asString asUppercase
  834. ! !
  835. !CharacterArray methodsFor: 'copying'!
  836. , aString
  837. ^self asString, aString asString
  838. ! !
  839. !CharacterArray methodsFor: 'error handling'!
  840. errorReadOnly
  841. self error: 'Object is read-only'
  842. ! !
  843. !CharacterArray methodsFor: 'printing'!
  844. printOn: aStream
  845. self asString printOn: aStream
  846. ! !
  847. !CharacterArray methodsFor: 'streaming'!
  848. putOn: aStream
  849. aStream nextPutString: self
  850. ! !
  851. !CharacterArray class methodsFor: 'instance creation'!
  852. fromString: aString
  853. self subclassResponsibility
  854. ! !
  855. CharacterArray subclass: #String
  856. instanceVariableNames: ''
  857. package: 'Kernel-Collections'!
  858. !String commentStamp!
  859. I am an indexed collection of Characters. Unlike most Smalltalk dialects, Amber doesn't provide the Character class. Instead, elements of a String are single character strings.
  860. String inherits many useful methods from its hierarchy, such as
  861. `Collection >> #,`!
  862. !String methodsFor: 'accessing'!
  863. asciiValue
  864. <return self.charCodeAt(0);>
  865. !
  866. at: anIndex ifAbsent: aBlock
  867. <return String(self).charAt(anIndex - 1) || aBlock()>
  868. !
  869. at: anIndex ifPresent: aBlock ifAbsent: anotherBlock
  870. <
  871. var result = String(self).charAt(anIndex - 1);
  872. return result ? aBlock._value_(result) : anotherBlock._value();
  873. >
  874. !
  875. charCodeAt: anInteger
  876. < return self.charCodeAt(anInteger - 1) >
  877. !
  878. escaped
  879. <return escape(self)>
  880. !
  881. size
  882. <return self.length>
  883. !
  884. unescaped
  885. <return unescape(self)>
  886. ! !
  887. !String methodsFor: 'comparing'!
  888. < aString
  889. <return String(self) < aString._asString()>
  890. !
  891. <= aString
  892. <return String(self) <= aString._asString()>
  893. !
  894. = aString
  895. <
  896. if(typeof aString === 'undefined') { return false }
  897. if(!!aString._isString || !! aString._isString()) {
  898. return false;
  899. }
  900. return String(self) === String(aString)
  901. >
  902. !
  903. == aString
  904. ^self = aString
  905. !
  906. > aString
  907. <return String(self) >> aString._asString()>
  908. !
  909. >= aString
  910. <return String(self) >>= aString._asString()>
  911. ! !
  912. !String methodsFor: 'converting'!
  913. asJSON
  914. ^self
  915. !
  916. asJavascript
  917. <
  918. if(self.search(/^[a-zA-Z0-9_:.$ ]*$/) == -1)
  919. return "\"" + self.replace(/[\x00-\x1f"\\\x7f-\x9f]/g, function(ch){var c=ch.charCodeAt(0);return "\\x"+("0"+c.toString(16)).slice(-2)}) + "\"";
  920. else
  921. return "\"" + self + "\"";
  922. >
  923. !
  924. asLowercase
  925. <return self.toLowerCase()>
  926. !
  927. asNumber
  928. <return Number(self)>
  929. !
  930. asRegexp
  931. ^ RegularExpression fromString: self
  932. !
  933. asSelector
  934. <return smalltalk.selector(self)>
  935. !
  936. asString
  937. ^self
  938. !
  939. asSymbol
  940. ^ self
  941. !
  942. asUppercase
  943. <return self.toUpperCase()>
  944. !
  945. crlfSanitized
  946. ^self lines join: String lf
  947. !
  948. reversed
  949. <return self.split("").reverse().join("")>
  950. ! !
  951. !String methodsFor: 'copying'!
  952. , aString
  953. <return self + aString>
  954. !
  955. copyFrom: anIndex to: anotherIndex
  956. <return self.substring(anIndex - 1, anotherIndex)>
  957. !
  958. deepCopy
  959. ^self shallowCopy
  960. !
  961. shallowCopy
  962. ^self class fromString: self
  963. ! !
  964. !String methodsFor: 'enumerating'!
  965. do: aBlock
  966. <for(var i=0;i<self.length;i++){aBlock(self.charAt(i));}>
  967. !
  968. withIndexDo: aBlock
  969. <for(var i=0;i<self.length;i++){aBlock(self.charAt(i), i+1);}>
  970. ! !
  971. !String methodsFor: 'printing'!
  972. printNl
  973. <console.log(self)>
  974. !
  975. printOn: aStream
  976. aStream
  977. nextPutAll: '''';
  978. nextPutAll: self;
  979. nextPutAll: ''''
  980. ! !
  981. !String methodsFor: 'regular expressions'!
  982. match: aRegexp
  983. <return self.search(aRegexp) !!= -1>
  984. !
  985. matchesOf: aRegularExpression
  986. <return self.match(aRegularExpression)>
  987. !
  988. replace: aString with: anotherString
  989. ^self replaceRegexp: (RegularExpression fromString: aString flag: 'g') with: anotherString
  990. !
  991. replaceRegexp: aRegexp with: aString
  992. <return self.replace(aRegexp, aString)>
  993. !
  994. trimBoth
  995. ^self trimBoth: '\s'
  996. !
  997. trimBoth: separators
  998. ^(self trimLeft: separators) trimRight: separators
  999. !
  1000. trimLeft
  1001. ^self trimLeft: '\s'
  1002. !
  1003. trimLeft: separators
  1004. ^self replaceRegexp: (RegularExpression fromString: '^[', separators, ']+' flag: 'g') with: ''
  1005. !
  1006. trimRight
  1007. ^self trimRight: '\s'
  1008. !
  1009. trimRight: separators
  1010. ^self replaceRegexp: (RegularExpression fromString: '[', separators, ']+$' flag: 'g') with: ''
  1011. ! !
  1012. !String methodsFor: 'split join'!
  1013. join: aCollection
  1014. ^ String
  1015. streamContents: [:stream | aCollection
  1016. do: [:each | stream nextPutAll: each asString]
  1017. separatedBy: [stream nextPutAll: self]]
  1018. !
  1019. lineIndicesDo: aBlock
  1020. "execute aBlock with 3 arguments for each line:
  1021. - start index of line
  1022. - end index of line without line delimiter
  1023. - end index of line including line delimiter(s) CR, LF or CRLF"
  1024. | cr lf start sz nextLF nextCR |
  1025. start := 1.
  1026. sz := self size.
  1027. cr := String cr.
  1028. nextCR := self indexOf: cr startingAt: 1.
  1029. lf := String lf.
  1030. nextLF := self indexOf: lf startingAt: 1.
  1031. [ start <= sz ] whileTrue: [
  1032. (nextLF = 0 and: [ nextCR = 0 ])
  1033. ifTrue: [ "No more CR, nor LF, the string is over"
  1034. aBlock value: start value: sz value: sz.
  1035. ^self ].
  1036. (nextCR = 0 or: [ 0 < nextLF and: [ nextLF < nextCR ] ])
  1037. ifTrue: [ "Found a LF"
  1038. aBlock value: start value: nextLF - 1 value: nextLF.
  1039. start := 1 + nextLF.
  1040. nextLF := self indexOf: lf startingAt: start ]
  1041. ifFalse: [ 1 + nextCR = nextLF
  1042. ifTrue: [ "Found a CR-LF pair"
  1043. aBlock value: start value: nextCR - 1 value: nextLF.
  1044. start := 1 + nextLF.
  1045. nextCR := self indexOf: cr startingAt: start.
  1046. nextLF := self indexOf: lf startingAt: start ]
  1047. ifFalse: [ "Found a CR"
  1048. aBlock value: start value: nextCR - 1 value: nextCR.
  1049. start := 1 + nextCR.
  1050. nextCR := self indexOf: cr startingAt: start ]]]
  1051. !
  1052. lineNumber: anIndex
  1053. "Answer a string containing the characters in the given line number."
  1054. | lineCount |
  1055. lineCount := 0.
  1056. self lineIndicesDo: [:start :endWithoutDelimiters :end |
  1057. (lineCount := lineCount + 1) = anIndex ifTrue: [^self copyFrom: start to: endWithoutDelimiters]].
  1058. ^nil
  1059. !
  1060. lines
  1061. "Answer an array of lines composing this receiver without the line ending delimiters."
  1062. | lines |
  1063. lines := Array new.
  1064. self linesDo: [:aLine | lines add: aLine].
  1065. ^lines
  1066. !
  1067. linesDo: aBlock
  1068. "Execute aBlock with each line in this string. The terminating line
  1069. delimiters CR, LF or CRLF pairs are not included in what is passed to aBlock"
  1070. self lineIndicesDo: [:start :endWithoutDelimiters :end |
  1071. aBlock value: (self copyFrom: start to: endWithoutDelimiters)]
  1072. !
  1073. subStrings: aString
  1074. ^ self tokenize: aString
  1075. !
  1076. tokenize: aString
  1077. <return self.split(aString)>
  1078. ! !
  1079. !String methodsFor: 'testing'!
  1080. includesSubString: subString
  1081. < return self.indexOf(subString) !!= -1 >
  1082. !
  1083. isImmutable
  1084. ^ true
  1085. !
  1086. isString
  1087. ^true
  1088. !
  1089. isVowel
  1090. "Answer true if the receiver is a one character string containing a voyel"
  1091. ^ self size = 1 and: [ 'aeiou' includes: self asLowercase ]
  1092. ! !
  1093. !String class methodsFor: 'accessing'!
  1094. cr
  1095. <return '\r'>
  1096. !
  1097. crlf
  1098. <return '\r\n'>
  1099. !
  1100. lf
  1101. <return '\n'>
  1102. !
  1103. space
  1104. <return ' '>
  1105. !
  1106. streamClass
  1107. ^StringStream
  1108. !
  1109. tab
  1110. <return '\t'>
  1111. ! !
  1112. !String class methodsFor: 'instance creation'!
  1113. fromCharCode: anInteger
  1114. <return String.fromCharCode(anInteger)>
  1115. !
  1116. fromString: aString
  1117. <return String(aString)>
  1118. !
  1119. value: aUTFCharCode
  1120. <return String.fromCharCode(aUTFCharCode);>
  1121. ! !
  1122. !String class methodsFor: 'random'!
  1123. random
  1124. "Returns random alphanumeric string beginning with letter"
  1125. <return (Math.random()*(22/32)+(10/32)).toString(32).slice(2);>
  1126. !
  1127. randomNotIn: aString
  1128. | result |
  1129. [ result := self random. aString includesSubString: result ] whileTrue.
  1130. ^result
  1131. ! !
  1132. Collection subclass: #Set
  1133. instanceVariableNames: 'elements'
  1134. package: 'Kernel-Collections'!
  1135. !Set commentStamp!
  1136. I represent an unordered set of objects without duplicates.!
  1137. !Set methodsFor: 'accessing'!
  1138. size
  1139. ^elements size
  1140. ! !
  1141. !Set methodsFor: 'adding/removing'!
  1142. add: anObject
  1143. <
  1144. var found;
  1145. for(var i=0; i < self['@elements'].length; i++) {
  1146. if(anObject == self['@elements'][i]) {
  1147. found = true;
  1148. break;
  1149. }
  1150. }
  1151. if(!!found) {self['@elements'].push(anObject)}
  1152. >
  1153. !
  1154. remove: anObject
  1155. elements remove: anObject
  1156. ! !
  1157. !Set methodsFor: 'comparing'!
  1158. = aCollection
  1159. self class = aCollection class ifFalse: [ ^ false ].
  1160. self size = aCollection size ifFalse: [ ^ false ].
  1161. self do: [:each | (aCollection includes: each) ifFalse: [ ^ false ] ].
  1162. ^ true
  1163. ! !
  1164. !Set methodsFor: 'converting'!
  1165. asArray
  1166. ^elements copy
  1167. ! !
  1168. !Set methodsFor: 'enumerating'!
  1169. collect: aBlock
  1170. ^self class withAll: (elements collect: aBlock)
  1171. !
  1172. detect: aBlock ifNone: anotherBlock
  1173. ^elements detect: aBlock ifNone: anotherBlock
  1174. !
  1175. do: aBlock
  1176. elements do: aBlock
  1177. !
  1178. select: aBlock
  1179. | collection |
  1180. collection := self class new.
  1181. self do: [:each |
  1182. (aBlock value: each) ifTrue: [
  1183. collection add: each]].
  1184. ^collection
  1185. ! !
  1186. !Set methodsFor: 'initialization'!
  1187. initialize
  1188. super initialize.
  1189. elements := #()
  1190. ! !
  1191. !Set methodsFor: 'printing'!
  1192. printOn: aStream
  1193. super printOn: aStream.
  1194. aStream nextPutAll: ' ('.
  1195. self
  1196. do: [ :each | each printOn: aStream ]
  1197. separatedBy: [ aStream nextPutAll: ' ' ].
  1198. aStream nextPutAll: ')'
  1199. ! !
  1200. !Set methodsFor: 'testing'!
  1201. includes: anObject
  1202. ^elements includes: anObject
  1203. ! !
  1204. Object subclass: #Queue
  1205. instanceVariableNames: 'read readIndex write'
  1206. package: 'Kernel-Collections'!
  1207. !Queue commentStamp!
  1208. I am a one-sided queue.
  1209. ## Usage
  1210. Use `#nextPut:` to add items to the queue.
  1211. Use `#next` or `#nextIfAbsent:` to get (and remove) the next item in the queue.
  1212. ## Implementation notes
  1213. A Queue uses two OrderedCollections inside,
  1214. `read` is at the front, is not modified and only read using `readIndex`.
  1215. `write` is at the back and is appended new items.
  1216. When `read` is exhausted, `write` is promoted to `read` and new `write` is created.
  1217. As a consequence, no data moving is done by me, write appending may do data moving
  1218. when growing `write`, but this is left to engine to implement as good as it chooses to.!
  1219. !Queue methodsFor: 'accessing'!
  1220. next
  1221. ^self nextIfAbsent: [ self error: 'Cannot read from empty Queue.' ]
  1222. !
  1223. nextIfAbsent: aBlock
  1224. | result |
  1225. result := read at: readIndex ifAbsent: [
  1226. write isEmpty ifTrue: [
  1227. readIndex > 1 ifTrue: [ read := #(). readIndex := 1 ].
  1228. ^aBlock value ].
  1229. read := write.
  1230. readIndex := 1.
  1231. write := OrderedCollection new.
  1232. read first ].
  1233. read at: readIndex put: nil.
  1234. readIndex := readIndex + 1.
  1235. ^result
  1236. !
  1237. nextPut: anObject
  1238. write add: anObject
  1239. ! !
  1240. !Queue methodsFor: 'initialization'!
  1241. initialize
  1242. super initialize.
  1243. read := OrderedCollection new.
  1244. write := OrderedCollection new.
  1245. readIndex := 1
  1246. ! !
  1247. Object subclass: #RegularExpression
  1248. instanceVariableNames: ''
  1249. package: 'Kernel-Collections'!
  1250. !RegularExpression commentStamp!
  1251. I represent a regular expression object. My instances are JavaScript `RegExp` object.!
  1252. !RegularExpression methodsFor: 'evaluating'!
  1253. compile: aString
  1254. <return self.compile(aString)>
  1255. !
  1256. exec: aString
  1257. <return self.exec(aString) || nil>
  1258. !
  1259. test: aString
  1260. <return self.test(aString)>
  1261. ! !
  1262. !RegularExpression class methodsFor: 'instance creation'!
  1263. fromString: aString
  1264. ^self fromString: aString flag: ''
  1265. !
  1266. fromString: aString flag: anotherString
  1267. <return new RegExp(aString, anotherString)>
  1268. ! !
  1269. Object subclass: #Stream
  1270. instanceVariableNames: 'collection position streamSize'
  1271. package: 'Kernel-Collections'!
  1272. !Stream commentStamp!
  1273. I represent an accessor for a sequence of objects. This sequence is referred to as my "contents".
  1274. My instances are read/write streams to the contents sequence collection.!
  1275. !Stream methodsFor: 'accessing'!
  1276. collection
  1277. ^collection
  1278. !
  1279. contents
  1280. ^self collection
  1281. copyFrom: 1
  1282. to: self streamSize
  1283. !
  1284. position
  1285. ^position ifNil: [position := 0]
  1286. !
  1287. position: anInteger
  1288. position := anInteger
  1289. !
  1290. setCollection: aCollection
  1291. collection := aCollection
  1292. !
  1293. setStreamSize: anInteger
  1294. streamSize := anInteger
  1295. !
  1296. size
  1297. ^self streamSize
  1298. !
  1299. streamSize
  1300. ^streamSize
  1301. ! !
  1302. !Stream methodsFor: 'actions'!
  1303. close
  1304. !
  1305. flush
  1306. !
  1307. reset
  1308. self position: 0
  1309. !
  1310. resetContents
  1311. self reset.
  1312. self setStreamSize: 0
  1313. ! !
  1314. !Stream methodsFor: 'enumerating'!
  1315. do: aBlock
  1316. [self atEnd] whileFalse: [aBlock value: self next]
  1317. ! !
  1318. !Stream methodsFor: 'positioning'!
  1319. setToEnd
  1320. self position: self size
  1321. !
  1322. skip: anInteger
  1323. self position: ((self position + anInteger) min: self size max: 0)
  1324. ! !
  1325. !Stream methodsFor: 'reading'!
  1326. next
  1327. ^self atEnd
  1328. ifTrue: [nil]
  1329. ifFalse: [
  1330. self position: self position + 1.
  1331. collection at: self position]
  1332. !
  1333. next: anInteger
  1334. | tempCollection |
  1335. tempCollection := self collection class new.
  1336. anInteger timesRepeat: [
  1337. self atEnd ifFalse: [
  1338. tempCollection add: self next]].
  1339. ^tempCollection
  1340. !
  1341. peek
  1342. ^self atEnd ifFalse: [
  1343. self collection at: self position + 1]
  1344. ! !
  1345. !Stream methodsFor: 'testing'!
  1346. atEnd
  1347. ^self position = self size
  1348. !
  1349. atStart
  1350. ^self position = 0
  1351. !
  1352. isEmpty
  1353. ^self size = 0
  1354. ! !
  1355. !Stream methodsFor: 'writing'!
  1356. << anObject
  1357. self write: anObject
  1358. !
  1359. nextPut: anObject
  1360. self position: self position + 1.
  1361. self collection at: self position put: anObject.
  1362. self setStreamSize: (self streamSize max: self position)
  1363. !
  1364. nextPutAll: aCollection
  1365. aCollection do: [:each |
  1366. self nextPut: each]
  1367. !
  1368. nextPutString: aString
  1369. self nextPut: aString
  1370. !
  1371. write: anObject
  1372. anObject putOn: self
  1373. ! !
  1374. !Stream class methodsFor: 'instance creation'!
  1375. on: aCollection
  1376. ^self new
  1377. setCollection: aCollection;
  1378. setStreamSize: aCollection size;
  1379. yourself
  1380. ! !
  1381. Stream subclass: #StringStream
  1382. instanceVariableNames: ''
  1383. package: 'Kernel-Collections'!
  1384. !StringStream commentStamp!
  1385. I am a Stream specific to `String` objects.!
  1386. !StringStream methodsFor: 'reading'!
  1387. next: anInteger
  1388. | tempCollection |
  1389. tempCollection := self collection class new.
  1390. anInteger timesRepeat: [
  1391. self atEnd ifFalse: [
  1392. tempCollection := tempCollection, self next]].
  1393. ^tempCollection
  1394. ! !
  1395. !StringStream methodsFor: 'writing'!
  1396. cr
  1397. ^self nextPutAll: String cr
  1398. !
  1399. crlf
  1400. ^self nextPutAll: String crlf
  1401. !
  1402. lf
  1403. ^self nextPutAll: String lf
  1404. !
  1405. nextPut: aString
  1406. self nextPutAll: aString
  1407. !
  1408. nextPutAll: aString
  1409. | pre post |
  1410. self atEnd ifTrue: [ self setCollection: self collection, aString ] ifFalse: [
  1411. pre := self collection copyFrom: 1 to: self position.
  1412. post := self collection copyFrom: (self position + 1 + aString size) to: self collection size.
  1413. self setCollection: pre, aString, post
  1414. ].
  1415. self position: self position + aString size.
  1416. self setStreamSize: (self streamSize max: self position)
  1417. !
  1418. nextPutString: aString
  1419. self nextPutAll: aString
  1420. !
  1421. space
  1422. self nextPut: ' '
  1423. !
  1424. tab
  1425. ^self nextPutAll: String tab
  1426. ! !