Kernel-Collections.st 45 KB

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