Kernel-Collections.st 23 KB

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