Kernel-Collections.st 39 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070207120722073207420752076207720782079208020812082208320842085208620872088208920902091209220932094209520962097209820992100210121022103210421052106210721082109211021112112211321142115211621172118211921202121212221232124212521262127
  1. Smalltalk current createPackage: 'Kernel-Collections'!
  2. Object subclass: #Association
  3. instanceVariableNames: 'key value'
  4. package: 'Kernel-Collections'!
  5. !Association commentStamp!
  6. I represent a pair of associated objects, a key and a value. My instances can serve as entries in a dictionary.
  7. Instances can be created with the class-side method `#key:value:`!
  8. !Association methodsFor: 'accessing'!
  9. key
  10. ^ key
  11. !
  12. key: aKey
  13. key := aKey
  14. !
  15. value
  16. ^ value
  17. !
  18. value: aValue
  19. value := aValue
  20. ! !
  21. !Association methodsFor: 'comparing'!
  22. = anAssociation
  23. ^ self class = anAssociation class and: [
  24. self key = anAssociation key and: [
  25. self value = anAssociation value ]]
  26. ! !
  27. !Association methodsFor: 'printing'!
  28. printOn: aStream
  29. self key printOn: aStream.
  30. aStream nextPutAll: ' -> '.
  31. self value printOn: aStream
  32. ! !
  33. !Association class methodsFor: 'instance creation'!
  34. key: aKey value: aValue
  35. ^ self new
  36. key: aKey;
  37. value: aValue;
  38. yourself
  39. ! !
  40. Object subclass: #Collection
  41. instanceVariableNames: ''
  42. package: 'Kernel-Collections'!
  43. !Collection commentStamp!
  44. I am the abstract superclass of all classes that represent a group of elements.
  45. I provide a set of useful methods to the Collection hierarchy such as enumerating and converting methods.!
  46. !Collection methodsFor: 'accessing'!
  47. occurrencesOf: anObject
  48. "Answer how many of the receiver's elements are equal to anObject."
  49. | tally |
  50. tally := 0.
  51. self do: [ :each | anObject = each ifTrue: [ tally := tally + 1 ]].
  52. ^ tally
  53. !
  54. size
  55. self subclassResponsibility
  56. ! !
  57. !Collection methodsFor: 'adding/removing'!
  58. add: anObject
  59. self subclassResponsibility
  60. !
  61. addAll: aCollection
  62. aCollection do: [ :each |
  63. self add: each ].
  64. ^ aCollection
  65. !
  66. anyOne
  67. "Answer a representative sample of the receiver. This method can
  68. be helpful when needing to preinfer the nature of the contents of
  69. semi-homogeneous collections."
  70. self ifEmpty: [ self error: 'Collection is empty' ].
  71. self do: [ :each | ^ each ]
  72. !
  73. remove: anObject
  74. ^ self remove: anObject ifAbsent: [ self errorNotFound ]
  75. !
  76. remove: anObject ifAbsent: aBlock
  77. self subclassResponsibility
  78. !
  79. removeAll
  80. self subclassResponsibility
  81. ! !
  82. !Collection methodsFor: 'converting'!
  83. asArray
  84. ^ Array withAll: self
  85. !
  86. asJSON
  87. ^ self asArray collect: [ :each | each asJSON ]
  88. !
  89. asOrderedCollection
  90. ^ self asArray
  91. !
  92. asSet
  93. ^ Set withAll: self
  94. ! !
  95. !Collection methodsFor: 'copying'!
  96. , aCollection
  97. ^ self copy
  98. addAll: aCollection;
  99. yourself
  100. !
  101. copyWith: anObject
  102. ^ self copy add: anObject; yourself
  103. !
  104. copyWithAll: aCollection
  105. ^ self copy addAll: aCollection; yourself
  106. !
  107. copyWithoutAll: aCollection
  108. "Answer a copy of the receiver that does not contain any elements
  109. equal to those in aCollection."
  110. ^ self reject: [ :each | aCollection includes: each ]
  111. ! !
  112. !Collection methodsFor: 'enumerating'!
  113. allSatisfy: aBlock
  114. "Evaluate aBlock with the elements of the receiver.
  115. If aBlock returns false for any element return false.
  116. Otherwise return true."
  117. self do: [ :each | (aBlock value: each) ifFalse: [ ^ false ] ].
  118. ^ true
  119. !
  120. anySatisfy: aBlock
  121. "Evaluate aBlock with the elements of the receiver.
  122. If aBlock returns true for any element return true.
  123. Otherwise return false."
  124. self do: [ :each | (aBlock value: each) ifTrue: [ ^ true ] ].
  125. ^ false
  126. !
  127. collect: aBlock
  128. | stream |
  129. stream := self class new writeStream.
  130. self do: [ :each |
  131. stream nextPut: (aBlock value: each) ].
  132. ^ stream contents
  133. !
  134. detect: aBlock
  135. ^ self detect: aBlock ifNone: [ self errorNotFound ]
  136. !
  137. detect: aBlock ifNone: anotherBlock
  138. self subclassResponsibility
  139. !
  140. do: aBlock
  141. self subclassResponsibility
  142. !
  143. do: aBlock separatedBy: anotherBlock
  144. | actionBeforeElement |
  145. actionBeforeElement := [ actionBeforeElement := anotherBlock ].
  146. self do: [ :each |
  147. actionBeforeElement value.
  148. aBlock value: each ]
  149. !
  150. inject: anObject into: aBlock
  151. | result |
  152. result := anObject.
  153. self do: [ :each |
  154. result := aBlock value: result value: each ].
  155. ^ result
  156. !
  157. intersection: aCollection
  158. "Answer the set theoretic intersection of two collections."
  159. | set outputSet |
  160. set := self asSet.
  161. outputSet := Set new.
  162. aCollection do: [ :each |
  163. ((set includes: each) and: [ (outputSet includes: each) not ])
  164. ifTrue: [
  165. outputSet add: each ]].
  166. ^ self class withAll: outputSet asArray
  167. !
  168. noneSatisfy: aBlock
  169. "Evaluate aBlock with the elements of the receiver.
  170. If aBlock returns false for all elements return true.
  171. Otherwise return false"
  172. self do: [ :item | (aBlock value: item) ifTrue: [ ^ false ] ].
  173. ^ true
  174. !
  175. reject: aBlock
  176. ^ self select: [ :each | (aBlock value: each) = false ]
  177. !
  178. select: aBlock
  179. | stream |
  180. stream := self class new writeStream.
  181. self do: [ :each |
  182. (aBlock value: each) ifTrue: [
  183. stream nextPut: each ] ].
  184. ^ stream contents
  185. !
  186. select: selectBlock thenCollect: collectBlock
  187. | stream |
  188. stream := self class new writeStream.
  189. self do: [ :each |
  190. (selectBlock value: each) ifTrue: [
  191. stream nextPut: (collectBlock value: each) ] ].
  192. ^ stream contents
  193. ! !
  194. !Collection methodsFor: 'error handling'!
  195. errorNotFound
  196. self error: 'Object is not in the collection'
  197. ! !
  198. !Collection methodsFor: 'streaming'!
  199. putOn: aStream
  200. self do: [ :each | each putOn: aStream ]
  201. ! !
  202. !Collection methodsFor: 'testing'!
  203. contains: aBlock
  204. self deprecatedAPI.
  205. ^ self anySatisfy: aBlock
  206. !
  207. ifEmpty: aBlock
  208. "Evaluate the given block with the receiver as argument, answering its value if the receiver is empty, otherwise answer the receiver.
  209. Note that the fact that this method returns its argument in case the receiver is not empty allows one to write expressions like the following ones:
  210. self classifyMethodAs:
  211. (myProtocol ifEmpty: ['As yet unclassified'])"
  212. ^ self isEmpty
  213. ifTrue: aBlock
  214. ifFalse: [ self ]
  215. !
  216. ifEmpty: aBlock ifNotEmpty: anotherBlock
  217. ^ self isEmpty
  218. ifTrue: aBlock
  219. ifFalse: anotherBlock
  220. !
  221. ifNotEmpty: aBlock
  222. ^ self notEmpty
  223. ifTrue: aBlock
  224. ifFalse: [ self ]
  225. !
  226. ifNotEmpty: aBlock ifEmpty: anotherBlock
  227. ^ self notEmpty
  228. ifTrue: aBlock
  229. ifFalse: anotherBlock
  230. !
  231. includes: anObject
  232. ^ self anySatisfy: [ :each | each = anObject ]
  233. !
  234. isEmpty
  235. ^ self size = 0
  236. !
  237. notEmpty
  238. ^ self isEmpty not
  239. ! !
  240. !Collection class methodsFor: 'helios'!
  241. heliosClass
  242. ^ 'collection'
  243. ! !
  244. !Collection class methodsFor: 'instance creation'!
  245. new: anInteger
  246. ^ self new
  247. !
  248. with: anObject
  249. ^ self new
  250. add: anObject;
  251. yourself
  252. !
  253. with: anObject with: anotherObject
  254. ^ self new
  255. add: anObject;
  256. add: anotherObject;
  257. yourself
  258. !
  259. with: firstObject with: secondObject with: thirdObject
  260. ^ self new
  261. add: firstObject;
  262. add: secondObject;
  263. add: thirdObject;
  264. yourself
  265. !
  266. withAll: aCollection
  267. ^ self new
  268. addAll: aCollection;
  269. yourself
  270. ! !
  271. Collection subclass: #IndexableCollection
  272. instanceVariableNames: ''
  273. package: 'Kernel-Collections'!
  274. !IndexableCollection commentStamp!
  275. I am a key-value store collection, that is,
  276. I store values under indexes.
  277. As a rule of thumb, if a collection has `#at:` and `#at:put:`,
  278. it is an IndexableCollection.!
  279. !IndexableCollection methodsFor: 'accessing'!
  280. at: anIndex
  281. "Lookup the given index in the receiver.
  282. If it is present, answer the value stored at anIndex.
  283. Otherwise, raise an error."
  284. ^ self at: anIndex ifAbsent: [ self errorNotFound ]
  285. !
  286. at: anIndex ifAbsent: aBlock
  287. "Lookup the given index in the receiver.
  288. If it is present, answer the value stored at anIndex.
  289. Otherwise, answer the value of aBlock."
  290. self subclassResponsibility
  291. !
  292. at: aKey ifAbsentPut: aBlock
  293. ^ self at: aKey ifAbsent: [
  294. self at: aKey put: aBlock value ]
  295. !
  296. at: anIndex ifPresent: aBlock
  297. "Lookup the given index in the receiver.
  298. If it is present, answer the value of evaluating aBlock with the value stored at anIndex.
  299. Otherwise, answer nil."
  300. ^ self at: anIndex ifPresent: aBlock ifAbsent: [ nil ]
  301. !
  302. at: anIndex ifPresent: aBlock ifAbsent: anotherBlock
  303. "Lookup the given index in the receiver.
  304. If it is present, answer the value of evaluating aBlock with the value stored at anIndex.
  305. Otherwise, answer the value of anotherBlock."
  306. self subclassResponsibility
  307. !
  308. at: anIndex put: anObject
  309. "Store anObject under the given index in the receiver."
  310. self subclassResponsibility
  311. !
  312. indexOf: anObject
  313. "Lookup index at which anObject is stored in the receiver.
  314. If not present, raise an error."
  315. ^ self indexOf: anObject ifAbsent: [ self errorNotFound ]
  316. !
  317. indexOf: anObject ifAbsent: aBlock
  318. "Lookup index at which anObject is stored in the receiver.
  319. If not present, return value of executing aBlock."
  320. self subclassResponsibility
  321. ! !
  322. !IndexableCollection methodsFor: 'enumarating'!
  323. with: anotherCollection do: aBlock
  324. "Calls aBlock with every value from self
  325. and with indetically-indexed value from anotherCollection"
  326. self withIndexDo: [ :each :index |
  327. aBlock value: each value: (anotherCollection at: index) ]
  328. !
  329. withIndexDo: aBlock
  330. "Calls aBlock with every value from self
  331. and with its index as the second argument"
  332. self subclassResponsibility
  333. ! !
  334. IndexableCollection subclass: #AssociativeCollection
  335. instanceVariableNames: ''
  336. package: 'Kernel-Collections'!
  337. !AssociativeCollection commentStamp!
  338. I am a base class for object-indexed collections (Dictionary et.al.).!
  339. !AssociativeCollection methodsFor: 'accessing'!
  340. associations
  341. | associations |
  342. associations := #().
  343. self associationsDo: [ :each | associations add: each ].
  344. ^ associations
  345. !
  346. at: aKey ifPresent: aBlock ifAbsent: anotherBlock
  347. "Lookup the given key in the receiver.
  348. If it is present, answer the value of evaluating the oneArgBlock with the value associated with the key,
  349. otherwise answer the value of absentBlock."
  350. ^ (self includesKey: aKey)
  351. ifTrue: [ aBlock value: (self at: aKey) ]
  352. ifFalse: anotherBlock
  353. !
  354. indexOf: anObject ifAbsent: aBlock
  355. ^ self keys detect: [ :each | (self at: each) = anObject ] ifNone: aBlock
  356. !
  357. keyAtValue: anObject
  358. ^ self keyAtValue: anObject ifAbsent: [ self errorNotFound ]
  359. !
  360. keyAtValue: anObject ifAbsent: aBlock
  361. ^ self indexOf: anObject ifAbsent: aBlock
  362. !
  363. keys
  364. self subclassResponsibility
  365. !
  366. size
  367. ^ self keys size
  368. !
  369. values
  370. self subclassResponsibility
  371. ! !
  372. !AssociativeCollection methodsFor: 'adding/removing'!
  373. add: anAssociation
  374. self at: anAssociation key put: anAssociation value
  375. !
  376. addAll: anAssocitativeCollection
  377. super addAll: anAssocitativeCollection associations.
  378. ^ anAssocitativeCollection
  379. !
  380. remove: aKey ifAbsent: aBlock
  381. ^ self removeKey: aKey ifAbsent: aBlock
  382. !
  383. removeAll
  384. ^ self keys do: [ :each | self removeKey: each ]
  385. !
  386. removeKey: aKey
  387. ^ self remove: aKey
  388. !
  389. removeKey: aKey ifAbsent: aBlock
  390. self subclassResponsibility
  391. ! !
  392. !AssociativeCollection methodsFor: 'comparing'!
  393. = anAssocitativeCollection
  394. self class = anAssocitativeCollection class ifFalse: [ ^ false ].
  395. self size = anAssocitativeCollection size ifFalse: [ ^ false ].
  396. ^ self associations = anAssocitativeCollection associations
  397. ! !
  398. !AssociativeCollection methodsFor: 'converting'!
  399. asDictionary
  400. ^ Dictionary from: self associations
  401. !
  402. asHashedCollection
  403. ^ HashedCollection from: self associations
  404. !
  405. asJSON
  406. | c |
  407. c := HashedCollection new.
  408. self keysAndValuesDo: [ :key :value |
  409. c at: key put: value asJSON ].
  410. ^ c
  411. ! !
  412. !AssociativeCollection methodsFor: 'copying'!
  413. deepCopy
  414. | copy |
  415. copy := self class new.
  416. self keysAndValuesDo: [ :key :value |
  417. copy at: key put: value deepCopy ].
  418. ^ copy
  419. !
  420. shallowCopy
  421. | copy |
  422. copy := self class new.
  423. self keysAndValuesDo: [ :key :value |
  424. copy at: key put: value ].
  425. ^ copy
  426. ! !
  427. !AssociativeCollection methodsFor: 'enumerating'!
  428. associationsDo: aBlock
  429. self keysAndValuesDo: [ :key :value |
  430. aBlock value: (Association key: key value: value) ]
  431. !
  432. collect: aBlock
  433. | newDict |
  434. newDict := self class new.
  435. self keysAndValuesDo: [ :key :value |
  436. newDict at: key put: (aBlock value: value) ].
  437. ^ newDict
  438. !
  439. detect: aBlock ifNone: anotherBlock
  440. ^ self values detect: aBlock ifNone: anotherBlock
  441. !
  442. do: aBlock
  443. self valuesDo: aBlock
  444. !
  445. includes: anObject
  446. ^ self values includes: anObject
  447. !
  448. keysAndValuesDo: aBlock
  449. self keysDo: [ :each |
  450. aBlock value: each value: (self at: each) ]
  451. !
  452. keysDo: aBlock
  453. self subclassResponsibility
  454. !
  455. select: aBlock
  456. | newDict |
  457. newDict := self class new.
  458. self keysAndValuesDo: [ :key :value |
  459. (aBlock value: value) ifTrue: [ newDict at: key put: value ]].
  460. ^ newDict
  461. !
  462. valuesDo: aBlock
  463. self subclassResponsibility
  464. !
  465. withIndexDo: aBlock
  466. self keysAndValuesDo: [ :key :value | aBlock value: value value: key ]
  467. ! !
  468. !AssociativeCollection methodsFor: 'printing'!
  469. printOn: aStream
  470. super printOn: aStream.
  471. aStream nextPutAll: ' ('.
  472. self associations
  473. do: [ :each | each printOn: aStream ]
  474. separatedBy: [ aStream nextPutAll: ' , ' ].
  475. aStream nextPutAll: ')'
  476. ! !
  477. !AssociativeCollection methodsFor: 'testing'!
  478. includesKey: aKey
  479. self subclassResponsibility
  480. ! !
  481. !AssociativeCollection class methodsFor: 'instance creation'!
  482. from: aCollection
  483. | newCollection |
  484. newCollection := self new.
  485. aCollection do: [ :each | newCollection add: each ].
  486. ^ newCollection
  487. !
  488. fromPairs: aCollection
  489. "This message is poorly named and has been replaced by #from:"
  490. ^ self from: aCollection
  491. !
  492. newFromPairs: aCollection
  493. "Accept an array of elements where every two elements form an
  494. association - the odd element being the key, and the even element the value."
  495. | newCollection |
  496. aCollection size even ifFalse: [
  497. self error: '#newFromPairs only accepts arrays of an even length' ].
  498. newCollection := self new.
  499. ( 1 to: aCollection size by: 2 ) do: [ :each |
  500. newCollection at: (aCollection at: each) put: (aCollection at: each + 1) ].
  501. ^ newCollection
  502. ! !
  503. AssociativeCollection subclass: #Dictionary
  504. instanceVariableNames: 'keys values'
  505. package: 'Kernel-Collections'!
  506. !Dictionary commentStamp!
  507. I represent a set of elements that can be viewed from one of two perspectives: a set of associations,
  508. or a container of values that are externally named where the name can be any object that responds to `=`.
  509. The external name is referred to as the key.!
  510. !Dictionary methodsFor: 'accessing'!
  511. at: aKey ifAbsent: aBlock
  512. <
  513. var index = self._positionOfKey_(aKey);
  514. return index >>=0 ? self['@values'][index] : aBlock._value();
  515. >
  516. !
  517. at: aKey put: aValue
  518. <
  519. var index = self._positionOfKey_(aKey);
  520. if(index === -1) {
  521. var keys = self['@keys'];
  522. index = keys.length;
  523. keys.push(aKey);
  524. }
  525. return self['@values'][index] = aValue;
  526. >
  527. !
  528. indexOf: anObject ifAbsent: aBlock
  529. | index |
  530. index := values
  531. indexOf: anObject
  532. ifAbsent: [ 0 ].
  533. ^ index = 0
  534. ifTrue: [ aBlock value ]
  535. ifFalse: [ keys at: index ]
  536. !
  537. keys
  538. ^ keys copy
  539. !
  540. values
  541. ^ values
  542. ! !
  543. !Dictionary methodsFor: 'adding/removing'!
  544. removeAll
  545. keys removeAll.
  546. values removeAll
  547. !
  548. removeKey: aKey ifAbsent: aBlock
  549. <
  550. var index = self._positionOfKey_(aKey);
  551. if(index === -1) {
  552. return aBlock._value()
  553. } else {
  554. var keys = self['@keys'], values = self['@values'];
  555. var value = values[index], l = keys.length;
  556. keys[index] = keys[l-1];
  557. keys.pop();
  558. values[index] = values[l-1];
  559. values.pop();
  560. return value;
  561. }
  562. >
  563. ! !
  564. !Dictionary methodsFor: 'enumerating'!
  565. keysAndValuesDo: aBlock
  566. ^ keys with: values do: aBlock
  567. !
  568. keysDo: aBlock
  569. ^ keys do: aBlock
  570. !
  571. valuesDo: aBlock
  572. ^ values do: aBlock
  573. ! !
  574. !Dictionary methodsFor: 'initialization'!
  575. initialize
  576. super initialize.
  577. keys := #().
  578. values := #()
  579. ! !
  580. !Dictionary methodsFor: 'private'!
  581. positionOfKey: anObject
  582. <
  583. var keys = self['@keys'];
  584. for(var i=0;i<keys.length;i++){
  585. if(keys[i].__eq(anObject)) { return i;}
  586. }
  587. return -1;
  588. >
  589. ! !
  590. !Dictionary methodsFor: 'testing'!
  591. includesKey: aKey
  592. < return self._positionOfKey_(aKey) >>= 0; >
  593. ! !
  594. AssociativeCollection subclass: #HashedCollection
  595. instanceVariableNames: ''
  596. package: 'Kernel-Collections'!
  597. !HashedCollection commentStamp!
  598. I am a traditional JavaScript object, or a Smalltalk `Dictionary`.
  599. Unlike a `Dictionary`, I can only have strings as keys.!
  600. !HashedCollection methodsFor: 'accessing'!
  601. at: aKey ifAbsent: aBlock
  602. ^ (self includesKey: aKey)
  603. ifTrue: [ self basicAt: aKey ]
  604. ifFalse: aBlock
  605. !
  606. at: aKey put: aValue
  607. ^ self basicAt: aKey put: aValue
  608. !
  609. keys
  610. <return Object.keys(self)>
  611. !
  612. values
  613. <
  614. return self._keys().map(function(key){
  615. return self._at_(key);
  616. });
  617. >
  618. ! !
  619. !HashedCollection methodsFor: 'adding/removing'!
  620. removeKey: aKey ifAbsent: aBlock
  621. ^ self
  622. at: aKey
  623. ifPresent: [ :removed | self basicDelete: aKey. removed ]
  624. ifAbsent: [ aBlock value ]
  625. ! !
  626. !HashedCollection methodsFor: 'enumerating'!
  627. keysDo: aBlock
  628. self keys do: aBlock
  629. !
  630. valuesDo: aBlock
  631. self values do: aBlock
  632. ! !
  633. !HashedCollection methodsFor: 'testing'!
  634. includesKey: aKey
  635. <return self.hasOwnProperty(aKey)>
  636. ! !
  637. IndexableCollection subclass: #SequenceableCollection
  638. instanceVariableNames: ''
  639. package: 'Kernel-Collections'!
  640. !SequenceableCollection commentStamp!
  641. I am an IndexableCollection
  642. with numeric indexes starting with 1.!
  643. !SequenceableCollection methodsFor: 'accessing'!
  644. allButFirst
  645. ^ self copyFrom: 2 to: self size
  646. !
  647. allButLast
  648. ^ self copyFrom: 1 to: self size - 1
  649. !
  650. atRandom
  651. ^ self at: self size atRandom
  652. !
  653. first
  654. ^ self at: 1
  655. !
  656. first: aNumber
  657. "Answer the first `aNumber` elements of the receiver.
  658. Raise an error if there are not enough elements in the receiver."
  659. self size < aNumber ifTrue: [ self error: 'Invalid number of elements' ].
  660. ^ self copyFrom: 1 to: aNumber
  661. !
  662. fourth
  663. ^ self at: 4
  664. !
  665. indexOf: anObject ifAbsent: aBlock
  666. <
  667. self = self._numericallyIndexable();
  668. for(var i=0; i < self.length; i++) {
  669. if(self[i].__eq(anObject)) {return i+1}
  670. };
  671. return aBlock._value();
  672. >
  673. !
  674. indexOf: anObject startingAt: start
  675. "Answer the index of the first occurence of anElement after start
  676. within the receiver. If the receiver does not contain anElement,
  677. answer 0."
  678. ^ self indexOf: anObject startingAt: start ifAbsent: [ 0 ]
  679. !
  680. indexOf: anObject startingAt: start ifAbsent: aBlock
  681. <
  682. self = self._numericallyIndexable();
  683. for(var i=start - 1; i < self.length; i++){
  684. if(self[i].__eq(anObject)) {return i+1}
  685. }
  686. return aBlock._value();
  687. >
  688. !
  689. last
  690. ^ self at: self size
  691. !
  692. last: aNumber
  693. "Answer the last aNumber elements of the receiver.
  694. Raise an error if there are not enough elements in the receiver."
  695. self size < aNumber ifTrue: [ self error: 'Invalid number of elements' ].
  696. ^ self copyFrom: self size - aNumber + 1 to: self size
  697. !
  698. second
  699. ^ self at: 2
  700. !
  701. third
  702. ^ self at: 3
  703. ! !
  704. !SequenceableCollection methodsFor: 'adding/removing'!
  705. addLast: anObject
  706. self add: anObject
  707. !
  708. removeLast
  709. ^ self remove: self last
  710. ! !
  711. !SequenceableCollection methodsFor: 'comparing'!
  712. = aCollection
  713. (self class = aCollection class and: [
  714. self size = aCollection size ]) ifFalse: [ ^ false ].
  715. self withIndexDo: [ :each :i |
  716. (aCollection at: i) = each ifFalse: [ ^ false ]].
  717. ^ true
  718. ! !
  719. !SequenceableCollection methodsFor: 'converting'!
  720. reversed
  721. self subclassResponsibility
  722. ! !
  723. !SequenceableCollection methodsFor: 'copying'!
  724. copyFrom: anIndex to: anotherIndex
  725. | range newCollection |
  726. range := anIndex to: anotherIndex.
  727. newCollection := self class new: range size.
  728. range withIndexDo: [ :each :i |
  729. newCollection at: i put: (self at: each) ].
  730. ^ newCollection
  731. !
  732. deepCopy
  733. | newCollection |
  734. newCollection := self class new: self size.
  735. self withIndexDo: [ :each :index |
  736. newCollection at: index put: each deepCopy ].
  737. ^ newCollection
  738. !
  739. shallowCopy
  740. | newCollection |
  741. newCollection := self class new: self size.
  742. self withIndexDo: [ :each :index |
  743. newCollection at: index put: each ].
  744. ^ newCollection
  745. ! !
  746. !SequenceableCollection methodsFor: 'enumerating'!
  747. detect: aBlock ifNone: anotherBlock
  748. <
  749. self = self._numericallyIndexable();
  750. for(var i = 0; i < self.length; i++)
  751. if(aBlock._value_(self[i]))
  752. return self[i];
  753. return anotherBlock._value();
  754. >
  755. !
  756. do: aBlock
  757. <
  758. self = self._numericallyIndexable();
  759. for(var i=0; i < self.length; i++) {
  760. aBlock._value_(self[i]);
  761. }
  762. >
  763. !
  764. with: anotherCollection do: aBlock
  765. <
  766. self = self._numericallyIndexable();
  767. anotherCollection = anotherCollection._numericallyIndexable();
  768. for(var i=0; i<self.length; i++) {
  769. aBlock._value_value_(self[i], anotherCollection[i]);
  770. }
  771. >
  772. !
  773. withIndexDo: aBlock
  774. <
  775. self = self._numericallyIndexable();
  776. for(var i=0; i < self.length; i++) {
  777. aBlock._value_value_(self[i], i+1);
  778. }
  779. >
  780. ! !
  781. !SequenceableCollection methodsFor: 'private'!
  782. numericallyIndexable
  783. "This is an internal converting message.
  784. It answeres a representation of the receiver
  785. that can use foo[i] in JavaScript code.
  786. It fixes IE8, where boxed String is unable
  787. to numerically index its characters,
  788. but primitive string can."
  789. self subclassResponsibility
  790. ! !
  791. !SequenceableCollection methodsFor: 'streaming'!
  792. newStream
  793. ^ self streamClass on: self
  794. !
  795. readStream
  796. "For Pharo compatibility"
  797. ^ self stream
  798. !
  799. stream
  800. ^ self newStream
  801. !
  802. streamClass
  803. ^ self class streamClass
  804. !
  805. writeStream
  806. "For Pharo compatibility"
  807. ^ self stream
  808. ! !
  809. !SequenceableCollection methodsFor: 'testing'!
  810. beginsWith: prefix
  811. self size < prefix size ifTrue: [ ^ false ].
  812. ^ (self first: prefix size) = prefix
  813. !
  814. endsWith: suffix
  815. self size < suffix size ifTrue: [ ^ false ].
  816. ^ (self last: suffix size) = suffix
  817. !
  818. includes: anObject
  819. ^ (self indexOf: anObject ifAbsent: [ nil ]) notNil
  820. ! !
  821. !SequenceableCollection class methodsFor: 'accessing'!
  822. streamClass
  823. ^ Stream
  824. ! !
  825. !SequenceableCollection class methodsFor: 'streaming'!
  826. streamContents: aBlock
  827. | stream |
  828. stream := (self streamClass on: self new).
  829. aBlock value: stream.
  830. ^ stream contents
  831. ! !
  832. SequenceableCollection subclass: #Array
  833. instanceVariableNames: ''
  834. package: 'Kernel-Collections'!
  835. !Array commentStamp!
  836. I represent a collection of objects ordered by the collector. The size of arrays is dynamic.
  837. I am directly mapped to JavaScript Number.
  838. *Note* In Amber, `OrderedCollection` is an alias for `Array`.!
  839. !Array methodsFor: 'accessing'!
  840. at: anIndex ifAbsent: aBlock
  841. <
  842. return anIndex >>= 1 && anIndex <= self.length
  843. ? self[anIndex - 1]
  844. : aBlock._value()
  845. >
  846. !
  847. at: anIndex ifPresent: aBlock ifAbsent: anotherBlock
  848. <
  849. return anIndex >>= 1 && anIndex <= self.length
  850. ? aBlock._value_(self[anIndex - 1])
  851. : anotherBlock._value()
  852. >
  853. !
  854. at: anIndex put: anObject
  855. <return self[anIndex - 1] = anObject>
  856. !
  857. size
  858. <return self.length>
  859. ! !
  860. !Array methodsFor: 'adding/removing'!
  861. add: anObject
  862. <self.push(anObject); return anObject;>
  863. !
  864. addFirst: anObject
  865. <self.unshift(anObject); return anObject;>
  866. !
  867. remove: anObject ifAbsent: aBlock
  868. <
  869. for(var i=0;i<self.length;i++) {
  870. if(_st(self[i]).__eq(anObject)) {
  871. self.splice(i,1);
  872. return self;
  873. }
  874. };
  875. aBlock._value();
  876. >
  877. !
  878. removeAll
  879. <self.length = 0>
  880. !
  881. removeFrom: aNumber to: anotherNumber
  882. <self.splice(aNumber -1, anotherNumber - aNumber + 1)>
  883. !
  884. removeIndex: anInteger
  885. <self.splice(anInteger - 1, 1)>
  886. !
  887. removeLast
  888. <return self.pop();>
  889. ! !
  890. !Array methodsFor: 'converting'!
  891. asJavascript
  892. ^ '[', ((self collect: [:each | each asJavascript ]) join: ', '), ']'
  893. !
  894. reversed
  895. <return self._copy().reverse()>
  896. ! !
  897. !Array methodsFor: 'enumerating'!
  898. collect: aBlock
  899. "Optimized version"
  900. <return self.map(function(each) {return aBlock._value_(each)})>
  901. !
  902. join: aString
  903. <return self.join(aString)>
  904. !
  905. select: aBlock
  906. "Optimized version"
  907. <
  908. var result = self.klass._new();
  909. for(var i=0; i<self.length; i++) {
  910. if(aBlock._value_(self[i])) {
  911. result.push(self[i]);
  912. }
  913. }
  914. return result;
  915. >
  916. !
  917. sort
  918. ^ self basicPerform: 'sort'
  919. !
  920. sort: aBlock
  921. <
  922. return self.sort(function(a, b) {
  923. if(aBlock._value_value_(a,b)) {return -1} else {return 1}
  924. })
  925. >
  926. !
  927. sorted
  928. ^ self copy sort
  929. !
  930. sorted: aBlock
  931. ^ self copy sort: aBlock
  932. ! !
  933. !Array methodsFor: 'printing'!
  934. printOn: aStream
  935. super printOn: aStream.
  936. aStream nextPutAll: ' ('.
  937. self
  938. do: [ :each | each printOn: aStream ]
  939. separatedBy: [ aStream nextPutAll: ' ' ].
  940. aStream nextPutAll: ')'
  941. ! !
  942. !Array methodsFor: 'private'!
  943. numericallyIndexable
  944. ^ self
  945. ! !
  946. !Array class methodsFor: 'instance creation'!
  947. new: anInteger
  948. <return new Array(anInteger)>
  949. !
  950. with: anObject
  951. ^ (self new: 1)
  952. at: 1 put: anObject;
  953. yourself
  954. !
  955. with: anObject with: anObject2
  956. ^ (self new: 2)
  957. at: 1 put: anObject;
  958. at: 2 put: anObject2;
  959. yourself
  960. !
  961. with: anObject with: anObject2 with: anObject3
  962. ^ (self new: 3)
  963. at: 1 put: anObject;
  964. at: 2 put: anObject2;
  965. at: 3 put: anObject3;
  966. yourself
  967. !
  968. withAll: aCollection
  969. | instance index |
  970. index := 1.
  971. instance := self new: aCollection size.
  972. aCollection do: [ :each |
  973. instance at: index put: each.
  974. index := index + 1 ].
  975. ^ instance
  976. ! !
  977. SequenceableCollection subclass: #CharacterArray
  978. instanceVariableNames: ''
  979. package: 'Kernel-Collections'!
  980. !CharacterArray commentStamp!
  981. I am the abstract superclass of string-like collections.!
  982. !CharacterArray methodsFor: 'accessing'!
  983. at: anIndex put: anObject
  984. self errorReadOnly
  985. ! !
  986. !CharacterArray methodsFor: 'adding/removing'!
  987. add: anObject
  988. self errorReadOnly
  989. !
  990. remove: anObject
  991. self errorReadOnly
  992. ! !
  993. !CharacterArray methodsFor: 'converting'!
  994. asLowercase
  995. ^ self class fromString: self asString asLowercase
  996. !
  997. asNumber
  998. ^ self asString asNumber
  999. !
  1000. asString
  1001. ^ self subclassResponsibility
  1002. !
  1003. asSymbol
  1004. ^ self asString
  1005. !
  1006. asUppercase
  1007. ^ self class fromString: self asString asUppercase
  1008. ! !
  1009. !CharacterArray methodsFor: 'copying'!
  1010. , aString
  1011. ^ self asString, aString asString
  1012. ! !
  1013. !CharacterArray methodsFor: 'error handling'!
  1014. errorReadOnly
  1015. self error: 'Object is read-only'
  1016. ! !
  1017. !CharacterArray methodsFor: 'printing'!
  1018. printOn: aStream
  1019. self asString printOn: aStream
  1020. ! !
  1021. !CharacterArray methodsFor: 'streaming'!
  1022. putOn: aStream
  1023. aStream nextPutString: self
  1024. ! !
  1025. !CharacterArray class methodsFor: 'instance creation'!
  1026. fromString: aString
  1027. self subclassResponsibility
  1028. ! !
  1029. CharacterArray subclass: #String
  1030. instanceVariableNames: ''
  1031. package: 'Kernel-Collections'!
  1032. !String commentStamp!
  1033. I am an indexed collection of Characters. Unlike most Smalltalk dialects, Amber doesn't provide the Character class. Instead, elements of a String are single character strings.
  1034. String inherits many useful methods from its hierarchy, such as
  1035. `Collection >> #,`!
  1036. !String methodsFor: 'accessing'!
  1037. asciiValue
  1038. <return self.charCodeAt(0);>
  1039. !
  1040. at: anIndex ifAbsent: aBlock
  1041. <return String(self)[anIndex - 1] || aBlock._value()>
  1042. !
  1043. at: anIndex ifPresent: aBlock ifAbsent: anotherBlock
  1044. <
  1045. var result = String(self)[anIndex - 1];
  1046. return result ? aBlock._value_(result) : anotherBlock._value();
  1047. >
  1048. !
  1049. charCodeAt: anInteger
  1050. <return self.charCodeAt(anInteger - 1)>
  1051. !
  1052. identityHash
  1053. ^ self, 's'
  1054. !
  1055. size
  1056. <return self.length>
  1057. ! !
  1058. !String methodsFor: 'comparing'!
  1059. < aString
  1060. <return String(self) < aString._asString()>
  1061. !
  1062. <= aString
  1063. <return String(self) <= aString._asString()>
  1064. !
  1065. = aString
  1066. <
  1067. if(typeof aString === 'undefined') { return false }
  1068. if(!!aString._isString || !! aString._isString()) {
  1069. return false;
  1070. }
  1071. return String(self) === String(aString)
  1072. >
  1073. !
  1074. == aString
  1075. ^ self = aString
  1076. !
  1077. > aString
  1078. <return String(self) >> aString._asString()>
  1079. !
  1080. >= aString
  1081. <return String(self) >>= aString._asString()>
  1082. ! !
  1083. !String methodsFor: 'converting'!
  1084. asJSON
  1085. ^ self
  1086. !
  1087. asJavascript
  1088. <
  1089. if(self.search(/^[a-zA-Z0-9_:.$ ]*$/) == -1)
  1090. return "\"" + self.replace(/[\x00-\x1f"\\\x7f-\x9f]/g, function(ch){var c=ch.charCodeAt(0);return "\\x"+("0"+c.toString(16)).slice(-2)}) + "\"";
  1091. else
  1092. return "\"" + self + "\"";
  1093. >
  1094. !
  1095. asLowercase
  1096. <return self.toLowerCase()>
  1097. !
  1098. asMutator
  1099. "Answer a setter selector. For example,
  1100. #name asMutator returns #name:"
  1101. self last = ':' ifFalse: [ ^ self, ':' ].
  1102. ^ self
  1103. !
  1104. asNumber
  1105. <return Number(self)>
  1106. !
  1107. asRegexp
  1108. ^ RegularExpression fromString: self
  1109. !
  1110. asSelector
  1111. <return smalltalk.selector(self)>
  1112. !
  1113. asString
  1114. ^ self
  1115. !
  1116. asSymbol
  1117. ^ self
  1118. !
  1119. asUppercase
  1120. <return self.toUpperCase()>
  1121. !
  1122. capitalized
  1123. ^ self isEmpty
  1124. ifTrue: [ self ]
  1125. ifFalse: [ self first asUppercase, self allButFirst ]
  1126. !
  1127. crlfSanitized
  1128. ^ self lines join: String lf
  1129. !
  1130. escaped
  1131. <return escape(self)>
  1132. !
  1133. reversed
  1134. <return self.split("").reverse().join("")>
  1135. !
  1136. unescaped
  1137. <return unescape(self)>
  1138. !
  1139. uriComponentDecoded
  1140. <return decodeURIComponent(self)>
  1141. !
  1142. uriComponentEncoded
  1143. <return encodeURIComponent(self)>
  1144. !
  1145. uriDecoded
  1146. <return decodeURI(self)>
  1147. !
  1148. uriEncoded
  1149. <return encodeURI(self)>
  1150. ! !
  1151. !String methodsFor: 'copying'!
  1152. , aString
  1153. <return String(self) + aString>
  1154. !
  1155. copyFrom: anIndex to: anotherIndex
  1156. <return self.substring(anIndex - 1, anotherIndex)>
  1157. !
  1158. deepCopy
  1159. ^ self shallowCopy
  1160. !
  1161. shallowCopy
  1162. ^ self class fromString: self
  1163. ! !
  1164. !String methodsFor: 'printing'!
  1165. printNl
  1166. <console.log(self)>
  1167. !
  1168. printOn: aStream
  1169. aStream
  1170. nextPutAll: '''';
  1171. nextPutAll: self;
  1172. nextPutAll: ''''
  1173. ! !
  1174. !String methodsFor: 'private'!
  1175. numericallyIndexable
  1176. <return String(self)>
  1177. ! !
  1178. !String methodsFor: 'regular expressions'!
  1179. match: aRegexp
  1180. <return self.search(aRegexp) !!= -1>
  1181. !
  1182. matchesOf: aRegularExpression
  1183. <return self.match(aRegularExpression)>
  1184. !
  1185. replace: aString with: anotherString
  1186. ^ self replaceRegexp: (RegularExpression fromString: aString flag: 'g') with: anotherString
  1187. !
  1188. replaceRegexp: aRegexp with: aString
  1189. <return self.replace(aRegexp, aString)>
  1190. !
  1191. trimBoth
  1192. ^ self trimBoth: '\s'
  1193. !
  1194. trimBoth: separators
  1195. ^ (self trimLeft: separators) trimRight: separators
  1196. !
  1197. trimLeft
  1198. ^ self trimLeft: '\s'
  1199. !
  1200. trimLeft: separators
  1201. ^ self replaceRegexp: (RegularExpression fromString: '^[', separators, ']+' flag: 'g') with: ''
  1202. !
  1203. trimRight
  1204. ^ self trimRight: '\s'
  1205. !
  1206. trimRight: separators
  1207. ^ self replaceRegexp: (RegularExpression fromString: '[', separators, ']+$' flag: 'g') with: ''
  1208. ! !
  1209. !String methodsFor: 'split join'!
  1210. join: aCollection
  1211. ^ String
  1212. streamContents: [ :stream | aCollection
  1213. do: [ :each | stream nextPutAll: each asString ]
  1214. separatedBy: [ stream nextPutAll: self ]]
  1215. !
  1216. lineIndicesDo: aBlock
  1217. "execute aBlock with 3 arguments for each line:
  1218. - start index of line
  1219. - end index of line without line delimiter
  1220. - end index of line including line delimiter(s) CR, LF or CRLF"
  1221. | cr lf start sz nextLF nextCR |
  1222. start := 1.
  1223. sz := self size.
  1224. cr := String cr.
  1225. nextCR := self indexOf: cr startingAt: 1.
  1226. lf := String lf.
  1227. nextLF := self indexOf: lf startingAt: 1.
  1228. [ start <= sz ] whileTrue: [
  1229. (nextLF = 0 and: [ nextCR = 0 ])
  1230. ifTrue: [ "No more CR, nor LF, the string is over"
  1231. aBlock value: start value: sz value: sz.
  1232. ^ self ].
  1233. (nextCR = 0 or: [ 0 < nextLF and: [ nextLF < nextCR ] ])
  1234. ifTrue: [ "Found a LF"
  1235. aBlock value: start value: nextLF - 1 value: nextLF.
  1236. start := 1 + nextLF.
  1237. nextLF := self indexOf: lf startingAt: start ]
  1238. ifFalse: [ 1 + nextCR = nextLF
  1239. ifTrue: [ "Found a CR-LF pair"
  1240. aBlock value: start value: nextCR - 1 value: nextLF.
  1241. start := 1 + nextLF.
  1242. nextCR := self indexOf: cr startingAt: start.
  1243. nextLF := self indexOf: lf startingAt: start ]
  1244. ifFalse: [ "Found a CR"
  1245. aBlock value: start value: nextCR - 1 value: nextCR.
  1246. start := 1 + nextCR.
  1247. nextCR := self indexOf: cr startingAt: start ] ]]
  1248. !
  1249. lineNumber: anIndex
  1250. "Answer a string containing the characters in the given line number."
  1251. | lineCount |
  1252. lineCount := 0.
  1253. self lineIndicesDo: [ :start :endWithoutDelimiters :end |
  1254. (lineCount := lineCount + 1) = anIndex ifTrue: [ ^ self copyFrom: start to: endWithoutDelimiters ]].
  1255. ^ nil
  1256. !
  1257. lines
  1258. "Answer an array of lines composing this receiver without the line ending delimiters."
  1259. | lines |
  1260. lines := Array new.
  1261. self linesDo: [ :aLine | lines add: aLine ].
  1262. ^ lines
  1263. !
  1264. linesDo: aBlock
  1265. "Execute aBlock with each line in this string. The terminating line
  1266. delimiters CR, LF or CRLF pairs are not included in what is passed to aBlock"
  1267. self lineIndicesDo: [ :start :endWithoutDelimiters :end |
  1268. aBlock value: (self copyFrom: start to: endWithoutDelimiters) ]
  1269. !
  1270. subStrings: aString
  1271. ^ self tokenize: aString
  1272. !
  1273. tokenize: aString
  1274. <return self.split(aString)>
  1275. ! !
  1276. !String methodsFor: 'testing'!
  1277. includesSubString: subString
  1278. <return self.indexOf(subString) !!= -1>
  1279. !
  1280. isCapitalized
  1281. ^ self first asUppercase == self first
  1282. !
  1283. isImmutable
  1284. ^ true
  1285. !
  1286. isString
  1287. ^ true
  1288. !
  1289. isVowel
  1290. "Answer true if the receiver is a one character string containing a voyel"
  1291. ^ self size = 1 and: [ 'aeiou' includes: self asLowercase ]
  1292. ! !
  1293. !String class methodsFor: 'accessing'!
  1294. cr
  1295. <return '\r'>
  1296. !
  1297. crlf
  1298. <return '\r\n'>
  1299. !
  1300. esc
  1301. ^ self fromCharCode: 27
  1302. !
  1303. lf
  1304. <return '\n'>
  1305. !
  1306. space
  1307. <return ' '>
  1308. !
  1309. streamClass
  1310. ^ StringStream
  1311. !
  1312. tab
  1313. <return '\t'>
  1314. ! !
  1315. !String class methodsFor: 'instance creation'!
  1316. fromCharCode: anInteger
  1317. <return String.fromCharCode(anInteger)>
  1318. !
  1319. fromString: aString
  1320. <return String(aString)>
  1321. !
  1322. value: aUTFCharCode
  1323. <return String.fromCharCode(aUTFCharCode);>
  1324. ! !
  1325. !String class methodsFor: 'random'!
  1326. random
  1327. "Returns random alphanumeric string beginning with letter"
  1328. <return (Math.random()*(22/32)+(10/32)).toString(32).slice(2);>
  1329. !
  1330. randomNotIn: aString
  1331. | result |
  1332. [ result := self random. aString includesSubString: result ] whileTrue.
  1333. ^ result
  1334. ! !
  1335. Collection subclass: #Set
  1336. instanceVariableNames: 'elements'
  1337. package: 'Kernel-Collections'!
  1338. !Set commentStamp!
  1339. I represent an unordered set of objects without duplicates.!
  1340. !Set methodsFor: 'accessing'!
  1341. size
  1342. ^ elements size
  1343. ! !
  1344. !Set methodsFor: 'adding/removing'!
  1345. add: anObject
  1346. <
  1347. var found;
  1348. for(var i=0; i < self['@elements'].length; i++) {
  1349. if(_st(anObject).__eq(self['@elements'][i])) {
  1350. found = true;
  1351. break;
  1352. }
  1353. }
  1354. if(!!found) {self['@elements'].push(anObject)}
  1355. >
  1356. !
  1357. remove: anObject
  1358. elements remove: anObject
  1359. !
  1360. remove: anObject ifAbsent: aBlock
  1361. elements remove: anObject ifAbsent: aBlock
  1362. !
  1363. removeAll
  1364. elements removeAll
  1365. ! !
  1366. !Set methodsFor: 'comparing'!
  1367. = aCollection
  1368. self class = aCollection class ifFalse: [ ^ false ].
  1369. self size = aCollection size ifFalse: [ ^ false ].
  1370. self do: [ :each | (aCollection includes: each) ifFalse: [ ^ false ] ].
  1371. ^ true
  1372. ! !
  1373. !Set methodsFor: 'converting'!
  1374. asArray
  1375. ^ elements copy
  1376. ! !
  1377. !Set methodsFor: 'enumerating'!
  1378. collect: aBlock
  1379. ^ self class withAll: (elements collect: aBlock)
  1380. !
  1381. detect: aBlock ifNone: anotherBlock
  1382. ^ elements detect: aBlock ifNone: anotherBlock
  1383. !
  1384. do: aBlock
  1385. elements do: aBlock
  1386. !
  1387. select: aBlock
  1388. | collection |
  1389. collection := self class new.
  1390. self do: [ :each |
  1391. (aBlock value: each) ifTrue: [
  1392. collection add: each ]].
  1393. ^ collection
  1394. ! !
  1395. !Set methodsFor: 'initialization'!
  1396. initialize
  1397. super initialize.
  1398. elements := #()
  1399. ! !
  1400. !Set methodsFor: 'printing'!
  1401. printOn: aStream
  1402. super printOn: aStream.
  1403. aStream nextPutAll: ' ('.
  1404. self
  1405. do: [ :each | each printOn: aStream ]
  1406. separatedBy: [ aStream nextPutAll: ' ' ].
  1407. aStream nextPutAll: ')'
  1408. ! !
  1409. !Set methodsFor: 'testing'!
  1410. includes: anObject
  1411. ^ elements includes: anObject
  1412. ! !
  1413. Object subclass: #Queue
  1414. instanceVariableNames: 'read readIndex write'
  1415. package: 'Kernel-Collections'!
  1416. !Queue commentStamp!
  1417. I am a one-sided queue.
  1418. ## Usage
  1419. Use `#nextPut:` to add items to the queue.
  1420. Use `#next` or `#nextIfAbsent:` to get (and remove) the next item in the queue.
  1421. ## Implementation notes
  1422. A Queue uses two OrderedCollections inside,
  1423. `read` is at the front, is not modified and only read using `readIndex`.
  1424. `write` is at the back and is appended new items.
  1425. When `read` is exhausted, `write` is promoted to `read` and new `write` is created.
  1426. As a consequence, no data moving is done by me, write appending may do data moving
  1427. when growing `write`, but this is left to engine to implement as good as it chooses to.!
  1428. !Queue methodsFor: 'accessing'!
  1429. next
  1430. ^ self nextIfAbsent: [ self error: 'Cannot read from empty Queue.' ]
  1431. !
  1432. nextIfAbsent: aBlock
  1433. | result |
  1434. result := read at: readIndex ifAbsent: [
  1435. write isEmpty ifTrue: [
  1436. readIndex > 1 ifTrue: [ read := #(). readIndex := 1 ].
  1437. ^ aBlock value ].
  1438. read := write.
  1439. readIndex := 1.
  1440. write := OrderedCollection new.
  1441. read first ].
  1442. read at: readIndex put: nil.
  1443. readIndex := readIndex + 1.
  1444. ^ result
  1445. !
  1446. nextPut: anObject
  1447. write add: anObject
  1448. ! !
  1449. !Queue methodsFor: 'initialization'!
  1450. initialize
  1451. super initialize.
  1452. read := OrderedCollection new.
  1453. write := OrderedCollection new.
  1454. readIndex := 1
  1455. ! !
  1456. Object subclass: #RegularExpression
  1457. instanceVariableNames: ''
  1458. package: 'Kernel-Collections'!
  1459. !RegularExpression commentStamp!
  1460. I represent a regular expression object. My instances are JavaScript `RegExp` object.!
  1461. !RegularExpression methodsFor: 'evaluating'!
  1462. compile: aString
  1463. <return self.compile(aString)>
  1464. !
  1465. exec: aString
  1466. <return self.exec(aString) || nil>
  1467. !
  1468. test: aString
  1469. <return self.test(aString)>
  1470. ! !
  1471. !RegularExpression class methodsFor: 'instance creation'!
  1472. fromString: aString
  1473. ^ self fromString: aString flag: ''
  1474. !
  1475. fromString: aString flag: anotherString
  1476. <return new RegExp(aString, anotherString)>
  1477. ! !
  1478. Object subclass: #Stream
  1479. instanceVariableNames: 'collection position streamSize'
  1480. package: 'Kernel-Collections'!
  1481. !Stream commentStamp!
  1482. I represent an accessor for a sequence of objects. This sequence is referred to as my "contents".
  1483. My instances are read/write streams to the contents sequence collection.!
  1484. !Stream methodsFor: 'accessing'!
  1485. collection
  1486. ^ collection
  1487. !
  1488. contents
  1489. ^ self collection
  1490. copyFrom: 1
  1491. to: self streamSize
  1492. !
  1493. position
  1494. ^ position ifNil: [ position := 0 ]
  1495. !
  1496. position: anInteger
  1497. position := anInteger
  1498. !
  1499. setCollection: aCollection
  1500. collection := aCollection
  1501. !
  1502. setStreamSize: anInteger
  1503. streamSize := anInteger
  1504. !
  1505. size
  1506. ^ self streamSize
  1507. !
  1508. streamSize
  1509. ^ streamSize
  1510. ! !
  1511. !Stream methodsFor: 'actions'!
  1512. close
  1513. !
  1514. flush
  1515. !
  1516. reset
  1517. self position: 0
  1518. !
  1519. resetContents
  1520. self reset.
  1521. self setStreamSize: 0
  1522. ! !
  1523. !Stream methodsFor: 'enumerating'!
  1524. do: aBlock
  1525. [ self atEnd ] whileFalse: [ aBlock value: self next ]
  1526. ! !
  1527. !Stream methodsFor: 'positioning'!
  1528. setToEnd
  1529. self position: self size
  1530. !
  1531. skip: anInteger
  1532. self position: ((self position + anInteger) min: self size max: 0)
  1533. ! !
  1534. !Stream methodsFor: 'reading'!
  1535. next
  1536. ^ self atEnd
  1537. ifTrue: [ nil ]
  1538. ifFalse: [
  1539. self position: self position + 1.
  1540. collection at: self position ]
  1541. !
  1542. next: anInteger
  1543. | tempCollection |
  1544. tempCollection := self collection class new.
  1545. anInteger timesRepeat: [
  1546. self atEnd ifFalse: [
  1547. tempCollection add: self next ]].
  1548. ^ tempCollection
  1549. !
  1550. peek
  1551. ^ self atEnd ifFalse: [
  1552. self collection at: self position + 1 ]
  1553. ! !
  1554. !Stream methodsFor: 'testing'!
  1555. atEnd
  1556. ^ self position = self size
  1557. !
  1558. atStart
  1559. ^ self position = 0
  1560. !
  1561. isEmpty
  1562. ^ self size = 0
  1563. ! !
  1564. !Stream methodsFor: 'writing'!
  1565. << anObject
  1566. self write: anObject
  1567. !
  1568. nextPut: anObject
  1569. self position: self position + 1.
  1570. self collection at: self position put: anObject.
  1571. self setStreamSize: (self streamSize max: self position)
  1572. !
  1573. nextPutAll: aCollection
  1574. aCollection do: [ :each |
  1575. self nextPut: each ]
  1576. !
  1577. nextPutString: aString
  1578. self nextPut: aString
  1579. !
  1580. write: anObject
  1581. anObject putOn: self
  1582. ! !
  1583. !Stream class methodsFor: 'instance creation'!
  1584. on: aCollection
  1585. ^ self new
  1586. setCollection: aCollection;
  1587. setStreamSize: aCollection size;
  1588. yourself
  1589. ! !
  1590. Stream subclass: #StringStream
  1591. instanceVariableNames: ''
  1592. package: 'Kernel-Collections'!
  1593. !StringStream commentStamp!
  1594. I am a Stream specific to `String` objects.!
  1595. !StringStream methodsFor: 'reading'!
  1596. next: anInteger
  1597. | tempCollection |
  1598. tempCollection := self collection class new.
  1599. anInteger timesRepeat: [
  1600. self atEnd ifFalse: [
  1601. tempCollection := tempCollection, self next ]].
  1602. ^ tempCollection
  1603. ! !
  1604. !StringStream methodsFor: 'writing'!
  1605. cr
  1606. ^ self nextPutAll: String cr
  1607. !
  1608. crlf
  1609. ^ self nextPutAll: String crlf
  1610. !
  1611. lf
  1612. ^ self nextPutAll: String lf
  1613. !
  1614. nextPut: aString
  1615. self nextPutAll: aString
  1616. !
  1617. nextPutAll: aString
  1618. | pre post |
  1619. self atEnd ifTrue: [ self setCollection: self collection, aString ] ifFalse: [
  1620. pre := self collection copyFrom: 1 to: self position.
  1621. post := self collection copyFrom: (self position + 1 + aString size) to: self collection size.
  1622. self setCollection: pre, aString, post
  1623. ].
  1624. self position: self position + aString size.
  1625. self setStreamSize: (self streamSize max: self position)
  1626. !
  1627. nextPutString: aString
  1628. self nextPutAll: aString
  1629. !
  1630. space
  1631. self nextPut: ' '
  1632. !
  1633. tab
  1634. ^ self nextPutAll: String tab
  1635. ! !