1
0

Kernel-Collections.st 28 KB

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