Kernel-Collections.st 48 KB

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