Kernel-Collections.st 30 KB

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