Kernel-Collections.st 36 KB

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