Kernel-Collections.st 34 KB

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