Kernel-Collections.st 34 KB

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