1
0

Kernel-Collections.st 27 KB

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