Kernel-Collections.st 48 KB

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