Kernel-Collections.st 35 KB

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