Kernel-Collections.st 22 KB

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