Kernel-Collections.st 28 KB

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