Kernel-Collections.st 46 KB

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