1
0

Kernel-Collections.st 28 KB

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