1
0

Kernel-Collections.st 28 KB

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