Kernel-Collections.st 36 KB

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