Kernel-Collections.st 37 KB

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