Kernel-Collections.st 28 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713
  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. 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. 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. asSymbol
  583. ^Symbol lookup: self
  584. !
  585. asJSON
  586. ^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. asJSON
  777. ^self asString asJSON
  778. ! !
  779. !Symbol methodsFor: 'copying'!
  780. copyFrom: anIndex to: anotherIndex
  781. ^self class fromString: (self asString copyFrom: anIndex to: anotherIndex)
  782. !
  783. deepCopy
  784. ^self
  785. !
  786. shallowCopy
  787. ^self
  788. ! !
  789. !Symbol methodsFor: 'printing'!
  790. printString
  791. ^'#', self asString
  792. !
  793. isSymbol
  794. ^true
  795. ! !
  796. !Symbol class methodsFor: 'instance creation'!
  797. lookup: aString
  798. <return smalltalk.symbolFor(aString);>
  799. !
  800. basicNew
  801. self shouldNotImplement
  802. !
  803. fromString: aString
  804. ^self lookup: aString
  805. ! !
  806. SequenceableCollection subclass: #Array
  807. instanceVariableNames: ''
  808. category: 'Kernel-Collections'!
  809. !Array methodsFor: 'accessing'!
  810. size
  811. <return self.length>
  812. !
  813. at: anIndex put: anObject
  814. <return self[anIndex - 1] = anObject>
  815. !
  816. at: anIndex ifAbsent: aBlock
  817. <
  818. var value = self[anIndex - 1];
  819. if(value === undefined) {
  820. return aBlock();
  821. } else {
  822. return value;
  823. }
  824. >
  825. ! !
  826. !Array methodsFor: 'adding/removing'!
  827. add: anObject
  828. <self.push(anObject); return anObject;>
  829. !
  830. remove: anObject
  831. <
  832. for(var i=0;i<self.length;i++) {
  833. if(self[i] == anObject) {
  834. self.splice(i,1);
  835. break;
  836. }
  837. }
  838. >
  839. !
  840. removeFrom: aNumber to: anotherNumber
  841. <self.splice(aNumber - 1,anotherNumber - 1)>
  842. ! !
  843. !Array methodsFor: 'converting'!
  844. asJavascript
  845. ^'[', ((self collect: [:each | each asJavascript]) join: ', '), ']'
  846. !
  847. reversed
  848. <return self._copy().reverse()>
  849. ! !
  850. !Array methodsFor: 'enumerating'!
  851. join: aString
  852. <return self.join(aString)>
  853. !
  854. sort
  855. ^self basicPerform: 'sort'
  856. !
  857. sort: aBlock
  858. <
  859. return self.sort(function(a, b) {
  860. if(aBlock(a,b)) {return -1} else {return 1}
  861. })
  862. >
  863. !
  864. sorted
  865. ^self copy sort
  866. !
  867. sorted: aBlock
  868. ^self copy sort: aBlock
  869. ! !
  870. !Array class methodsFor: 'instance creation'!
  871. new: anInteger
  872. <return new Array(anInteger)>
  873. !
  874. with: anObject
  875. ^(self new: 1)
  876. at: 1 put: anObject;
  877. yourself
  878. !
  879. with: anObject with: anObject2
  880. ^(self new: 2)
  881. at: 1 put: anObject;
  882. at: 2 put: anObject2;
  883. yourself
  884. !
  885. with: anObject with: anObject2 with: anObject3
  886. ^(self new: 3)
  887. at: 1 put: anObject;
  888. at: 2 put: anObject2;
  889. at: 3 put: anObject3;
  890. yourself
  891. !
  892. withAll: aCollection
  893. | instance |
  894. instance := self new: aCollection size.
  895. aCollection withIndexDo: [:each :index |
  896. instance at: index put: each].
  897. ^instance
  898. ! !
  899. SequenceableCollection subclass: #Array
  900. instanceVariableNames: ''
  901. category: 'Kernel-Collections'!
  902. !Array methodsFor: 'accessing'!
  903. size
  904. <return self.length>
  905. !
  906. at: anIndex put: anObject
  907. <return self[anIndex - 1] = anObject>
  908. !
  909. at: anIndex ifAbsent: aBlock
  910. <
  911. var value = self[anIndex - 1];
  912. if(value === undefined) {
  913. return aBlock();
  914. } else {
  915. return value;
  916. }
  917. >
  918. ! !
  919. !Array methodsFor: 'adding/removing'!
  920. add: anObject
  921. <self.push(anObject); return anObject;>
  922. !
  923. remove: anObject
  924. <
  925. for(var i=0;i<self.length;i++) {
  926. if(self[i] == anObject) {
  927. self.splice(i,1);
  928. break;
  929. }
  930. }
  931. >
  932. !
  933. removeFrom: aNumber to: anotherNumber
  934. <self.splice(aNumber - 1,anotherNumber - 1)>
  935. ! !
  936. !Array methodsFor: 'converting'!
  937. asJavascript
  938. ^'[', ((self collect: [:each | each asJavascript]) join: ', '), ']'
  939. !
  940. reversed
  941. <return self._copy().reverse()>
  942. ! !
  943. !Array methodsFor: 'enumerating'!
  944. join: aString
  945. <return self.join(aString)>
  946. !
  947. sort
  948. ^self basicPerform: 'sort'
  949. !
  950. sort: aBlock
  951. <
  952. return self.sort(function(a, b) {
  953. if(aBlock(a,b)) {return -1} else {return 1}
  954. })
  955. >
  956. !
  957. sorted
  958. ^self copy sort
  959. !
  960. sorted: aBlock
  961. ^self copy sort: aBlock
  962. ! !
  963. !Array class methodsFor: 'instance creation'!
  964. new: anInteger
  965. <return new Array(anInteger)>
  966. !
  967. with: anObject
  968. ^(self new: 1)
  969. at: 1 put: anObject;
  970. yourself
  971. !
  972. with: anObject with: anObject2
  973. ^(self new: 2)
  974. at: 1 put: anObject;
  975. at: 2 put: anObject2;
  976. yourself
  977. !
  978. with: anObject with: anObject2 with: anObject3
  979. ^(self new: 3)
  980. at: 1 put: anObject;
  981. at: 2 put: anObject2;
  982. at: 3 put: anObject3;
  983. yourself
  984. !
  985. withAll: aCollection
  986. | instance |
  987. instance := self new: aCollection size.
  988. aCollection withIndexDo: [:each :index |
  989. instance at: index put: each].
  990. ^instance
  991. ! !
  992. Stream subclass: #StringStream
  993. instanceVariableNames: ''
  994. category: 'Kernel-Collections'!
  995. !StringStream methodsFor: 'reading'!
  996. next: anInteger
  997. | tempCollection |
  998. tempCollection := self collection class new.
  999. anInteger timesRepeat: [
  1000. self atEnd ifFalse: [
  1001. tempCollection := tempCollection, self next]].
  1002. ^tempCollection
  1003. ! !
  1004. !StringStream methodsFor: 'writing'!
  1005. nextPut: aString
  1006. self nextPutAll: aString
  1007. !
  1008. nextPutAll: aString
  1009. self setCollection:
  1010. (self collection copyFrom: 1 to: self position),
  1011. aString,
  1012. (self collection copyFrom: (self position + 1 + aString size) to: self collection size).
  1013. self position: self position + aString size.
  1014. self setStreamSize: (self streamSize max: self position)
  1015. !
  1016. cr
  1017. ^self nextPutAll: String cr
  1018. !
  1019. crlf
  1020. ^self nextPutAll: String crlf
  1021. !
  1022. lf
  1023. ^self nextPutAll: String lf
  1024. !
  1025. space
  1026. self nextPut: ' '
  1027. ! !
  1028. Collection subclass: #Set
  1029. instanceVariableNames: 'elements'
  1030. category: 'Kernel-Collections'!
  1031. !Set methodsFor: 'accessing'!
  1032. size
  1033. ^elements size
  1034. ! !
  1035. !Set methodsFor: 'adding/removing'!
  1036. add: anObject
  1037. <
  1038. var found;
  1039. for(var i=0; i < self['@elements'].length; i++) {
  1040. if(anObject == self['@elements'][i]) {
  1041. found = true;
  1042. break;
  1043. }
  1044. }
  1045. if(!!found) {self['@elements'].push(anObject)}
  1046. >
  1047. !
  1048. remove: anObject
  1049. elements remove: anObject
  1050. ! !
  1051. !Set methodsFor: 'comparing'!
  1052. = aCollection
  1053. ^self class = aCollection class and: [
  1054. elements = aCollection asArray]
  1055. ! !
  1056. !Set methodsFor: 'converting'!
  1057. asArray
  1058. ^elements copy
  1059. ! !
  1060. !Set methodsFor: 'enumerating'!
  1061. detect: aBlock ifNone: anotherBlock
  1062. ^elements detect: aBlock ifNone: anotherBlock
  1063. !
  1064. do: aBlock
  1065. elements do: aBlock
  1066. !
  1067. select: aBlock
  1068. | collection |
  1069. collection := self class new.
  1070. self do: [:each |
  1071. (aBlock value: each) ifTrue: [
  1072. collection add: each]].
  1073. ^collection
  1074. ! !
  1075. !Set methodsFor: 'initialization'!
  1076. initialize
  1077. super initialize.
  1078. elements := #()
  1079. ! !
  1080. !Set methodsFor: 'testing'!
  1081. includes: anObject
  1082. ^elements includes: anObject
  1083. ! !
  1084. Collection subclass: #HashedCollection
  1085. instanceVariableNames: ''
  1086. category: 'Kernel-Collections'!
  1087. !HashedCollection commentStamp!
  1088. A HashedCollection is a traditional JavaScript object, or a Smalltalk Dictionary.
  1089. Unlike a Dictionary, it can only have strings as keys.!
  1090. !HashedCollection methodsFor: 'accessing'!
  1091. size
  1092. ^self keys size
  1093. !
  1094. associations
  1095. | associations |
  1096. associations := #().
  1097. self keys do: [:each |
  1098. associations add: (Association key: each value: (self at: each))].
  1099. ^associations
  1100. !
  1101. keys
  1102. <
  1103. var keys = [];
  1104. for(var i in self) {
  1105. if(self.hasOwnProperty(i)) {
  1106. keys.push(i);
  1107. }
  1108. };
  1109. return keys;
  1110. >
  1111. !
  1112. values
  1113. ^self keys collect: [:each | self at: each]
  1114. !
  1115. at: aKey put: aValue
  1116. ^self basicAt: aKey put: aValue
  1117. !
  1118. at: aKey ifAbsent: aBlock
  1119. ^(self includesKey: aKey)
  1120. ifTrue: [self basicAt: aKey]
  1121. ifFalse: aBlock
  1122. !
  1123. at: aKey ifAbsentPut: aBlock
  1124. ^self at: aKey ifAbsent: [
  1125. self at: aKey put: aBlock value]
  1126. !
  1127. at: aKey ifPresent: aBlock
  1128. ^(self basicAt: aKey) ifNotNil: [aBlock value: (self at: aKey)]
  1129. !
  1130. at: aKey ifPresent: aBlock ifAbsent: anotherBlock
  1131. ^(self basicAt: aKey)
  1132. ifNil: anotherBlock
  1133. ifNotNil: [aBlock value: (self at: aKey)]
  1134. !
  1135. at: aKey
  1136. ^self at: aKey ifAbsent: [self errorNotFound]
  1137. ! !
  1138. !HashedCollection methodsFor: 'adding/removing'!
  1139. add: anAssociation
  1140. self at: anAssociation key put: anAssociation value
  1141. !
  1142. addAll: aHashedCollection
  1143. super addAll: aHashedCollection associations.
  1144. ^aHashedCollection
  1145. !
  1146. removeKey: aKey
  1147. self remove: aKey
  1148. !
  1149. remove: aKey ifAbsent: aBlock
  1150. ^self removeKey: aKey ifAbsent: aBlock
  1151. !
  1152. removeKey: aKey ifAbsent: aBlock
  1153. ^(self includesKey: aKey)
  1154. ifFalse: [aBlock value]
  1155. ifTrue: [self basicDelete: aKey]
  1156. ! !
  1157. !HashedCollection methodsFor: 'comparing'!
  1158. = aHashedCollection
  1159. self class = aHashedCollection class ifFalse: [^false].
  1160. self size = aHashedCollection size ifFalse: [^false].
  1161. ^self associations = aHashedCollection associations
  1162. ! !
  1163. !HashedCollection methodsFor: 'converting'!
  1164. asDictionary
  1165. ^Dictionary fromPairs: self associations
  1166. !
  1167. asJSON
  1168. | c |
  1169. c := self class new.
  1170. self keysAndValuesDo: [:key :value |
  1171. c at: key put: value asJSON].
  1172. ^c
  1173. ! !
  1174. !HashedCollection methodsFor: 'copying'!
  1175. shallowCopy
  1176. | copy |
  1177. copy := self class new.
  1178. self associationsDo: [:each |
  1179. copy at: each key put: each value].
  1180. ^copy
  1181. !
  1182. , aCollection
  1183. self shouldNotImplement
  1184. !
  1185. copyFrom: anIndex to: anotherIndex
  1186. self shouldNotImplement
  1187. !
  1188. deepCopy
  1189. | copy |
  1190. copy := self class new.
  1191. self associationsDo: [:each |
  1192. copy at: each key put: each value deepCopy].
  1193. ^copy
  1194. ! !
  1195. !HashedCollection methodsFor: 'enumerating'!
  1196. associationsDo: aBlock
  1197. self associations do: aBlock
  1198. !
  1199. keysAndValuesDo: aBlock
  1200. self associationsDo: [:each |
  1201. aBlock value: each key value: each value]
  1202. !
  1203. do: aBlock
  1204. self values do: aBlock
  1205. !
  1206. select: aBlock
  1207. | newDict |
  1208. newDict := self class new.
  1209. self keysAndValuesDo: [:key :value |
  1210. (aBlock value: value) ifTrue: [newDict at: key put: value]].
  1211. ^newDict
  1212. !
  1213. collect: aBlock
  1214. | newDict |
  1215. newDict := self class new.
  1216. self keysAndValuesDo: [:key :value |
  1217. newDict at: key put: (aBlock value: value)].
  1218. ^newDict
  1219. !
  1220. detect: aBlock ifNone: anotherBlock
  1221. ^self values detect: aBlock ifNone: anotherBlock
  1222. !
  1223. includes: anObject
  1224. ^self values includes: anObject
  1225. ! !
  1226. !HashedCollection methodsFor: 'printing'!
  1227. printString
  1228. ^String streamContents: [:aStream|
  1229. aStream
  1230. nextPutAll: super printString;
  1231. nextPutAll: '('.
  1232. self associations
  1233. do: [:anAssociation|
  1234. aStream
  1235. nextPutAll: anAssociation key printString;
  1236. nextPutAll: ' -> ';
  1237. nextPutAll: anAssociation value printString]
  1238. separatedBy: [aStream nextPutAll: ' , '].
  1239. aStream nextPutAll: ')']
  1240. !
  1241. storeOn: aStream
  1242. aStream nextPutAll: '#{'.
  1243. self associations
  1244. do: [:each | each storeOn: aStream]
  1245. separatedBy: [ aStream nextPutAll: '. '].
  1246. aStream nextPutAll: '}'
  1247. ! !
  1248. !HashedCollection methodsFor: 'testing'!
  1249. includesKey: aKey
  1250. <return self.hasOwnProperty(aKey)>
  1251. ! !
  1252. !HashedCollection class methodsFor: 'instance creation'!
  1253. fromPairs: aCollection
  1254. | dict |
  1255. dict := self new.
  1256. aCollection do: [:each | dict add: each].
  1257. ^dict
  1258. ! !
  1259. HashedCollection subclass: #Dictionary
  1260. instanceVariableNames: 'keys values'
  1261. category: 'Kernel-Collections'!
  1262. !Dictionary methodsFor: 'accessing'!
  1263. at: aKey ifAbsent: aBlock
  1264. <
  1265. var index;
  1266. for(var i=0;i<self['@keys'].length;i++){
  1267. if(self['@keys'][i].__eq(aKey)) {index = i;}
  1268. };
  1269. if(typeof index === 'undefined') {
  1270. return aBlock();
  1271. } else {
  1272. return self['@values'][index];
  1273. }
  1274. >
  1275. !
  1276. keys
  1277. ^keys copy
  1278. !
  1279. values
  1280. ^values copy
  1281. !
  1282. at: aKey put: aValue
  1283. <
  1284. var index = self['@keys'].indexOf(aKey);
  1285. if(index === -1) {
  1286. self['@values'].push(aValue);
  1287. self['@keys'].push(aKey);
  1288. } else {
  1289. self['@values'][index] = aValue;
  1290. };
  1291. return aValue;
  1292. >
  1293. ! !
  1294. !Dictionary methodsFor: 'adding/removing'!
  1295. removeKey: aKey ifAbsent: aBlock
  1296. <
  1297. var index = self['@keys'].indexOf(aKey);
  1298. if(index === -1) {
  1299. return aBlock()
  1300. } else {
  1301. self['@keys'].splice(i, 1);
  1302. self['@values'].splice(i, 1);
  1303. return aKey
  1304. };
  1305. >
  1306. ! !
  1307. !Dictionary methodsFor: 'converting'!
  1308. asHashedCollection
  1309. ^HashedCollection fromPairs: self associations
  1310. !
  1311. asJSON
  1312. ^self asHashedCollection asJSON
  1313. ! !
  1314. !Dictionary methodsFor: 'initialization'!
  1315. initialize
  1316. super initialize.
  1317. keys := #().
  1318. values := #()
  1319. ! !
  1320. !Dictionary methodsFor: 'testing'!
  1321. includesKey: aKey
  1322. ^keys includes: aKey
  1323. ! !