Kernel-Collections.st 27 KB

12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028102910301031103210331034103510361037103810391040104110421043104410451046104710481049105010511052105310541055105610571058105910601061106210631064106510661067106810691070107110721073107410751076107710781079108010811082108310841085108610871088108910901091109210931094109510961097109810991100110111021103110411051106110711081109111011111112111311141115111611171118111911201121112211231124112511261127112811291130113111321133113411351136113711381139114011411142114311441145114611471148114911501151115211531154115511561157115811591160116111621163116411651166116711681169117011711172117311741175117611771178117911801181118211831184118511861187118811891190119111921193119411951196119711981199120012011202120312041205120612071208120912101211121212131214121512161217121812191220122112221223122412251226122712281229123012311232123312341235123612371238123912401241124212431244124512461247124812491250125112521253125412551256125712581259126012611262126312641265126612671268126912701271127212731274127512761277127812791280128112821283128412851286128712881289129012911292129312941295129612971298129913001301130213031304130513061307130813091310131113121313131413151316131713181319132013211322132313241325132613271328132913301331133213331334133513361337133813391340134113421343134413451346134713481349135013511352135313541355135613571358135913601361136213631364136513661367136813691370137113721373137413751376137713781379138013811382138313841385138613871388138913901391139213931394139513961397139813991400140114021403140414051406140714081409141014111412141314141415141614171418141914201421142214231424142514261427142814291430143114321433143414351436143714381439144014411442144314441445144614471448144914501451145214531454145514561457145814591460146114621463146414651466146714681469147014711472147314741475147614771478147914801481148214831484148514861487148814891490149114921493149414951496149714981499150015011502150315041505150615071508150915101511151215131514151515161517151815191520152115221523152415251526152715281529153015311532153315341535153615371538153915401541154215431544154515461547154815491550155115521553155415551556155715581559156015611562156315641565156615671568156915701571157215731574157515761577157815791580158115821583158415851586158715881589159015911592159315941595159615971598159916001601160216031604160516061607160816091610161116121613161416151616161716181619162016211622162316241625162616271628162916301631163216331634163516361637163816391640164116421643164416451646164716481649165016511652165316541655165616571658165916601661166216631664166516661667166816691670167116721673
  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._asString()>
  364. !
  365. < aString
  366. <return String(self) < aString._asString()>
  367. !
  368. >= aString
  369. <return String(self) >>= aString._asString()>
  370. !
  371. <= aString
  372. <return String(self) <= aString._asString()>
  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. aSymbol class = self class ifFalse: [^false].
  596. ^self asString = aSymbol asString
  597. !
  598. > aSymbol
  599. ^self asString > aSymbol asString
  600. ! !
  601. !Symbol methodsFor: 'converting'!
  602. asString
  603. <return self.value>
  604. !
  605. asSymbol
  606. ^self
  607. !
  608. asJavascript
  609. ^'smalltalk.symbolFor("', self asString, '")'
  610. !
  611. asSelector
  612. ^self asString asSelector
  613. ! !
  614. !Symbol methodsFor: 'copying'!
  615. copyFrom: anIndex to: anotherIndex
  616. ^self class fromString: (self asString copyFrom: anIndex to: anotherIndex)
  617. !
  618. deepCopy
  619. ^self
  620. !
  621. shallowCopy
  622. ^self
  623. ! !
  624. !Symbol methodsFor: 'printing'!
  625. printString
  626. ^'#', self asString
  627. !
  628. isSymbol
  629. ^true
  630. ! !
  631. !Symbol class methodsFor: 'instance creation'!
  632. lookup: aString
  633. <return smalltalk.symbolFor(aString);>
  634. !
  635. basicNew
  636. self shouldNotImplement
  637. !
  638. fromString: aString
  639. ^self lookup: aString
  640. ! !
  641. SequenceableCollection subclass: #Array
  642. instanceVariableNames: ''
  643. category: 'Kernel-Collections'!
  644. !Array methodsFor: 'accessing'!
  645. size
  646. <return self.length>
  647. !
  648. at: anIndex put: anObject
  649. <return self[anIndex - 1] = anObject>
  650. !
  651. at: anIndex ifAbsent: aBlock
  652. <
  653. var value = self[anIndex - 1];
  654. if(value === undefined) {
  655. return aBlock();
  656. } else {
  657. return value;
  658. }
  659. >
  660. ! !
  661. !Array methodsFor: 'adding/removing'!
  662. add: anObject
  663. <self.push(anObject); return anObject;>
  664. !
  665. remove: anObject
  666. <
  667. for(var i=0;i<self.length;i++) {
  668. if(self[i] == anObject) {
  669. self.splice(i,1);
  670. break;
  671. }
  672. }
  673. >
  674. !
  675. removeFrom: aNumber to: anotherNumber
  676. <self.splice(aNumber - 1,anotherNumber - 1)>
  677. ! !
  678. !Array methodsFor: 'converting'!
  679. asJavascript
  680. ^'[', ((self collect: [:each | each asJavascript]) join: ', '), ']'
  681. !
  682. reversed
  683. <return self._copy().reverse()>
  684. ! !
  685. !Array methodsFor: 'enumerating'!
  686. join: aString
  687. <return self.join(aString)>
  688. !
  689. sort
  690. ^self basicPerform: 'sort'
  691. !
  692. sort: aBlock
  693. <
  694. return self.sort(function(a, b) {
  695. if(aBlock(a,b)) {return -1} else {return 1}
  696. })
  697. >
  698. !
  699. sorted
  700. ^self copy sort
  701. !
  702. sorted: aBlock
  703. ^self copy sort: aBlock
  704. ! !
  705. !Array class methodsFor: 'instance creation'!
  706. new: anInteger
  707. <return new Array(anInteger)>
  708. !
  709. with: anObject
  710. ^(self new: 1)
  711. at: 1 put: anObject;
  712. yourself
  713. !
  714. with: anObject with: anObject2
  715. ^(self new: 2)
  716. at: 1 put: anObject;
  717. at: 2 put: anObject2;
  718. yourself
  719. !
  720. with: anObject with: anObject2 with: anObject3
  721. ^(self new: 3)
  722. at: 1 put: anObject;
  723. at: 2 put: anObject2;
  724. at: 3 put: anObject3;
  725. yourself
  726. !
  727. withAll: aCollection
  728. | instance |
  729. instance := self new: aCollection size.
  730. aCollection withIndexDo: [:index :each |
  731. instance at: index put: each].
  732. ^instance
  733. ! !
  734. Object subclass: #RegularExpression
  735. instanceVariableNames: ''
  736. category: 'Kernel-Collections'!
  737. !RegularExpression methodsFor: 'evaluating'!
  738. compile: aString
  739. <return self.compile(aString)>
  740. !
  741. exec: aString
  742. <return self.exec(aString) || nil>
  743. !
  744. test: aString
  745. <return self.test(aString)>
  746. ! !
  747. !RegularExpression class methodsFor: 'instance creation'!
  748. fromString: aString flag: anotherString
  749. <return new RegExp(aString, anotherString)>
  750. !
  751. fromString: aString
  752. ^self fromString: aString flag: ''
  753. ! !
  754. Object subclass: #Association
  755. instanceVariableNames: 'key value'
  756. category: 'Kernel-Collections'!
  757. !Association methodsFor: 'accessing'!
  758. key: aKey
  759. key := aKey
  760. !
  761. key
  762. ^key
  763. !
  764. value: aValue
  765. value := aValue
  766. !
  767. value
  768. ^value
  769. ! !
  770. !Association methodsFor: 'comparing'!
  771. = anAssociation
  772. ^self class = anAssociation class and: [
  773. self key = anAssociation key and: [
  774. self value = anAssociation value]]
  775. !
  776. storeOn: aStream
  777. "Store in the format (key->value)"
  778. "aStream nextPutAll: '('."
  779. key storeOn: aStream.
  780. aStream nextPutAll: '->'.
  781. value storeOn: aStream.
  782. "aStream nextPutAll: ')'"
  783. ! !
  784. !Association class methodsFor: 'instance creation'!
  785. key: aKey value: aValue
  786. ^self new
  787. key: aKey;
  788. value: aValue;
  789. yourself
  790. ! !
  791. Object subclass: #Stream
  792. instanceVariableNames: 'collection position streamSize'
  793. category: 'Kernel-Collections'!
  794. !Stream methodsFor: 'accessing'!
  795. collection
  796. ^collection
  797. !
  798. setCollection: aCollection
  799. collection := aCollection
  800. !
  801. position
  802. ^position ifNil: [position := 0]
  803. !
  804. position: anInteger
  805. position := anInteger
  806. !
  807. streamSize
  808. ^streamSize
  809. !
  810. setStreamSize: anInteger
  811. streamSize := anInteger
  812. !
  813. contents
  814. ^self collection
  815. copyFrom: 1
  816. to: self streamSize
  817. !
  818. size
  819. ^self streamSize
  820. ! !
  821. !Stream methodsFor: 'actions'!
  822. reset
  823. self position: 0
  824. !
  825. close
  826. !
  827. flush
  828. !
  829. resetContents
  830. self reset.
  831. self setStreamSize: 0
  832. ! !
  833. !Stream methodsFor: 'enumerating'!
  834. do: aBlock
  835. [self atEnd] whileFalse: [aBlock value: self next]
  836. ! !
  837. !Stream methodsFor: 'positioning'!
  838. setToEnd
  839. self position: self size
  840. !
  841. skip: anInteger
  842. self position: ((self position + anInteger) min: self size max: 0)
  843. ! !
  844. !Stream methodsFor: 'reading'!
  845. next
  846. ^self atEnd
  847. ifTrue: [nil]
  848. ifFalse: [
  849. self position: self position + 1.
  850. collection at: self position]
  851. !
  852. next: anInteger
  853. | tempCollection |
  854. tempCollection := self collection class new.
  855. anInteger timesRepeat: [
  856. self atEnd ifFalse: [
  857. tempCollection add: self next]].
  858. ^tempCollection
  859. !
  860. peek
  861. ^self atEnd ifFalse: [
  862. self collection at: self position + 1]
  863. ! !
  864. !Stream methodsFor: 'testing'!
  865. atEnd
  866. ^self position = self size
  867. !
  868. atStart
  869. ^self position = 0
  870. !
  871. isEmpty
  872. ^self size = 0
  873. ! !
  874. !Stream methodsFor: 'writing'!
  875. nextPut: anObject
  876. self position: self position + 1.
  877. self collection at: self position put: anObject.
  878. self setStreamSize: (self streamSize max: self position)
  879. !
  880. nextPutAll: aCollection
  881. aCollection do: [:each |
  882. self nextPut: each]
  883. ! !
  884. !Stream class methodsFor: 'instance creation'!
  885. on: aCollection
  886. ^self new
  887. setCollection: aCollection;
  888. setStreamSize: aCollection size;
  889. yourself
  890. ! !
  891. Stream subclass: #StringStream
  892. instanceVariableNames: ''
  893. category: 'Kernel-Collections'!
  894. !StringStream methodsFor: 'reading'!
  895. next: anInteger
  896. | tempCollection |
  897. tempCollection := self collection class new.
  898. anInteger timesRepeat: [
  899. self atEnd ifFalse: [
  900. tempCollection := tempCollection, self next]].
  901. ^tempCollection
  902. ! !
  903. !StringStream methodsFor: 'writing'!
  904. nextPut: aString
  905. self nextPutAll: aString
  906. !
  907. nextPutAll: aString
  908. self setCollection:
  909. (self collection copyFrom: 1 to: self position),
  910. aString,
  911. (self collection copyFrom: (self position + 1 + aString size) to: self collection size).
  912. self position: self position + aString size.
  913. self setStreamSize: (self streamSize max: self position)
  914. !
  915. cr
  916. ^self nextPutAll: String cr
  917. !
  918. crlf
  919. ^self nextPutAll: String crlf
  920. !
  921. lf
  922. ^self nextPutAll: String lf
  923. !
  924. space
  925. self nextPut: ' '
  926. ! !
  927. Collection subclass: #Set
  928. instanceVariableNames: 'elements'
  929. category: 'Kernel-Collections'!
  930. !Set methodsFor: 'accessing'!
  931. size
  932. ^elements size
  933. ! !
  934. !Set methodsFor: 'adding/removing'!
  935. add: anObject
  936. <
  937. var found;
  938. for(var i in self['@elements']) {
  939. if(anObject == self['@elements'][i]) {
  940. found = true;
  941. break;
  942. }
  943. }
  944. if(!!found) {self['@elements'].push(anObject)}
  945. >
  946. !
  947. remove: anObject
  948. elements remove: anObject
  949. ! !
  950. !Set methodsFor: 'comparing'!
  951. = aCollection
  952. ^self class = aCollection class and: [
  953. elements = aCollection asArray]
  954. ! !
  955. !Set methodsFor: 'converting'!
  956. asArray
  957. ^elements copy
  958. ! !
  959. !Set methodsFor: 'enumerating'!
  960. detect: aBlock ifNone: anotherBlock
  961. ^elements detect: aBlock ifNone: anotherBlock
  962. !
  963. do: aBlock
  964. elements do: aBlock
  965. !
  966. select: aBlock
  967. | collection |
  968. collection := self class new.
  969. self do: [:each |
  970. (aBlock value: each) ifTrue: [
  971. collection add: each]].
  972. ^collection
  973. ! !
  974. !Set methodsFor: 'initialization'!
  975. initialize
  976. super initialize.
  977. elements := #()
  978. ! !
  979. !Set methodsFor: 'testing'!
  980. includes: anObject
  981. ^elements includes: anObject
  982. ! !
  983. Collection subclass: #HashedCollection
  984. instanceVariableNames: ''
  985. category: 'Kernel-Collections'!
  986. !HashedCollection commentStamp!
  987. A HashedCollection is a traditional JavaScript object, or a Smalltalk Dictionary.
  988. Unlike a Dictionary, it can only have strings as keys.!
  989. !HashedCollection methodsFor: 'accessing'!
  990. size
  991. ^self keys size
  992. !
  993. associations
  994. | associations |
  995. associations := #().
  996. self keys do: [:each |
  997. associations add: (Association key: each value: (self at: each))].
  998. ^associations
  999. !
  1000. keys
  1001. <
  1002. var keys = [];
  1003. for(var i in self) {
  1004. if(self.hasOwnProperty(i)) {
  1005. keys.push(i);
  1006. }
  1007. };
  1008. return keys;
  1009. >
  1010. !
  1011. values
  1012. ^self keys collect: [:each | self at: each]
  1013. !
  1014. at: aKey put: aValue
  1015. ^self basicAt: aKey put: aValue
  1016. !
  1017. at: aKey ifAbsent: aBlock
  1018. ^(self includesKey: aKey)
  1019. ifTrue: [self basicAt: aKey]
  1020. ifFalse: aBlock
  1021. !
  1022. at: aKey ifAbsentPut: aBlock
  1023. ^self at: aKey ifAbsent: [
  1024. self at: aKey put: aBlock value]
  1025. !
  1026. at: aKey ifPresent: aBlock
  1027. ^(self basicAt: aKey) ifNotNil: [aBlock value: (self at: aKey)]
  1028. !
  1029. at: aKey ifPresent: aBlock ifAbsent: anotherBlock
  1030. ^(self basicAt: aKey)
  1031. ifNil: anotherBlock
  1032. ifNotNil: [aBlock value: (self at: aKey)]
  1033. !
  1034. at: aKey
  1035. ^self at: aKey ifAbsent: [self errorNotFound]
  1036. ! !
  1037. !HashedCollection methodsFor: 'adding/removing'!
  1038. add: anAssociation
  1039. self at: anAssociation key put: anAssociation value
  1040. !
  1041. addAll: aHashedCollection
  1042. super addAll: aHashedCollection associations.
  1043. ^aHashedCollection
  1044. !
  1045. removeKey: aKey
  1046. self remove: aKey
  1047. !
  1048. remove: aKey ifAbsent: aBlock
  1049. ^self removeKey: aKey ifAbsent: aBlock
  1050. !
  1051. removeKey: aKey ifAbsent: aBlock
  1052. ^(self includesKey: aKey)
  1053. ifFalse: [aBlock value]
  1054. ifTrue: [self basicDelete: aKey]
  1055. ! !
  1056. !HashedCollection methodsFor: 'comparing'!
  1057. = aHashedCollection
  1058. self class = aHashedCollection class ifFalse: [^false].
  1059. self size = aHashedCollection size ifFalse: [^false].
  1060. ^self associations = aHashedCollection associations
  1061. ! !
  1062. !HashedCollection methodsFor: 'converting'!
  1063. asDictionary
  1064. ^Dictionary fromPairs: self associations
  1065. ! !
  1066. !HashedCollection methodsFor: 'copying'!
  1067. shallowCopy
  1068. | copy |
  1069. copy := self class new.
  1070. self associationsDo: [:each |
  1071. copy at: each key put: each value].
  1072. ^copy
  1073. !
  1074. , aCollection
  1075. self shouldNotImplement
  1076. !
  1077. copyFrom: anIndex to: anotherIndex
  1078. self shouldNotImplement
  1079. !
  1080. deepCopy
  1081. | copy |
  1082. copy := self class new.
  1083. self associationsDo: [:each |
  1084. copy at: each key put: each value deepCopy].
  1085. ^copy
  1086. ! !
  1087. !HashedCollection methodsFor: 'enumerating'!
  1088. associationsDo: aBlock
  1089. self associations do: aBlock
  1090. !
  1091. keysAndValuesDo: aBlock
  1092. self associationsDo: [:each |
  1093. aBlock value: each key value: each value]
  1094. !
  1095. do: aBlock
  1096. self values do: aBlock
  1097. !
  1098. select: aBlock
  1099. | newDict |
  1100. newDict := self class new.
  1101. self keysAndValuesDo: [:key :value |
  1102. (aBlock value: value) ifTrue: [newDict at: key put: value]].
  1103. ^newDict
  1104. !
  1105. collect: aBlock
  1106. | newDict |
  1107. newDict := self class new.
  1108. self keysAndValuesDo: [:key :value |
  1109. newDict at: key put: (aBlock value: value)].
  1110. ^newDict
  1111. !
  1112. detect: aBlock ifNone: anotherBlock
  1113. ^self values detect: aBlock ifNone: anotherBlock
  1114. !
  1115. includes: anObject
  1116. ^self values includes: anObject
  1117. ! !
  1118. !HashedCollection methodsFor: 'printing'!
  1119. printString
  1120. ^String streamContents: [:aStream|
  1121. aStream
  1122. nextPutAll: super printString;
  1123. nextPutAll: '('.
  1124. self associations
  1125. do: [:anAssociation|
  1126. aStream
  1127. nextPutAll: anAssociation key printString;
  1128. nextPutAll: ' -> ';
  1129. nextPutAll: anAssociation value printString]
  1130. separatedBy: [aStream nextPutAll: ' , '].
  1131. aStream nextPutAll: ')']
  1132. !
  1133. storeOn: aStream
  1134. aStream nextPutAll: '#{'.
  1135. self associations
  1136. do: [:each | each storeOn: aStream]
  1137. separatedBy: [ aStream nextPutAll: '. '].
  1138. aStream nextPutAll: '}'
  1139. ! !
  1140. !HashedCollection methodsFor: 'testing'!
  1141. includesKey: aKey
  1142. <return self.hasOwnProperty(aKey)>
  1143. ! !
  1144. !HashedCollection class methodsFor: 'instance creation'!
  1145. fromPairs: aCollection
  1146. | dict |
  1147. dict := self new.
  1148. aCollection do: [:each | dict add: each].
  1149. ^dict
  1150. ! !
  1151. HashedCollection subclass: #Dictionary
  1152. instanceVariableNames: 'keys values'
  1153. category: 'Kernel-Collections'!
  1154. !Dictionary methodsFor: 'accessing'!
  1155. at: aKey ifAbsent: aBlock
  1156. <
  1157. var index;
  1158. for(var i=0;i<self['@keys'].length;i++){
  1159. if(self['@keys'][i].__eq(aKey)) {index = i;}
  1160. };
  1161. if(typeof index === 'undefined') {
  1162. return aBlock();
  1163. } else {
  1164. return self['@values'][index];
  1165. }
  1166. >
  1167. !
  1168. keys
  1169. ^keys copy
  1170. !
  1171. values
  1172. ^values copy
  1173. !
  1174. at: aKey put: aValue
  1175. <
  1176. var index = self['@keys'].indexOf(aKey);
  1177. if(index === -1) {
  1178. self['@values'].push(aValue);
  1179. self['@keys'].push(aKey);
  1180. } else {
  1181. self['@values'][index] = aValue;
  1182. };
  1183. return aValue;
  1184. >
  1185. ! !
  1186. !Dictionary methodsFor: 'adding/removing'!
  1187. removeKey: aKey ifAbsent: aBlock
  1188. <
  1189. var index = self['@keys'].indexOf(aKey);
  1190. if(index === -1) {
  1191. return aBlock()
  1192. } else {
  1193. self['@keys'].splice(i, 1);
  1194. self['@values'].splice(i, 1);
  1195. return aKey
  1196. };
  1197. >
  1198. ! !
  1199. !Dictionary methodsFor: 'converting'!
  1200. asHashedCollection
  1201. ^HashedCollection fromPairs: self associations
  1202. !
  1203. asJSONString
  1204. ^self asHashedCollection asJSONString
  1205. ! !
  1206. !Dictionary methodsFor: 'initialization'!
  1207. initialize
  1208. super initialize.
  1209. keys := #().
  1210. values := #()
  1211. ! !
  1212. !Dictionary methodsFor: 'testing'!
  1213. includesKey: aKey
  1214. ^keys includes: aKey
  1215. ! !
  1216. SequenceableCollection subclass: #OrderedCollection
  1217. instanceVariableNames: 'elements'
  1218. category: 'Kernel-Collections'!
  1219. !OrderedCollection methodsFor: 'accessing'!
  1220. size
  1221. ^elements size
  1222. !
  1223. at: anIndex put: anObject
  1224. <return self['@elements'][anIndex - 1] = anObject>
  1225. !
  1226. at: anIndex ifAbsent: aBlock
  1227. ^elements at: anIndex ifAbsent: aBlock
  1228. ! !
  1229. !OrderedCollection methodsFor: 'adding/removing'!
  1230. add: anObject
  1231. <self['@elements'].push(anObject); return anObject;>
  1232. !
  1233. remove: anObject
  1234. <
  1235. for(var i=0;i<self['@elements'].length;i++) {
  1236. if(self['@elements'][i] == anObject) {
  1237. self['@elements'].splice(i,1);
  1238. break;
  1239. }
  1240. }
  1241. >
  1242. !
  1243. removeFrom: aNumber to: anotherNumber
  1244. <self['@elements'].splice(aNumber - 1,anotherNumber - 1)>
  1245. ! !
  1246. !OrderedCollection methodsFor: 'converting'!
  1247. reversed
  1248. ^self asArray reversed asOrderedCollection
  1249. !
  1250. asOrderedCollection
  1251. ^self
  1252. !
  1253. asArray
  1254. ^elements copy
  1255. ! !
  1256. !OrderedCollection methodsFor: 'enumerating'!
  1257. join: aString
  1258. ^elements join: aString
  1259. !
  1260. sort
  1261. elements sort.
  1262. ^self
  1263. !
  1264. sort: aBlock
  1265. elements sort: aBlock.
  1266. ^self
  1267. !
  1268. sorted
  1269. ^self copy sort
  1270. !
  1271. sorted: aBlock
  1272. ^self copy sort: aBlock
  1273. !
  1274. withIndexDo: aBlock
  1275. elements withIndexDo: aBlock
  1276. !
  1277. detect: aBlock ifNone: anotherBlock
  1278. ^elements detect: aBlock ifNone: anotherBlock
  1279. !
  1280. do: aBlock
  1281. elements do: aBlock
  1282. ! !
  1283. !OrderedCollection methodsFor: 'initialization'!
  1284. initialize
  1285. super initialize.
  1286. elements := #()
  1287. ! !