Kernel-Collections.st 33 KB

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