Kernel-Collections.st 48 KB

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