Kernel-Collections.st 28 KB

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