Kernel-Collections.st 30 KB

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