123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070207120722073207420752076207720782079208020812082208320842085208620872088208920902091209220932094209520962097209820992100210121022103210421052106210721082109211021112112211321142115211621172118211921202121212221232124212521262127212821292130213121322133213421352136213721382139214021412142214321442145214621472148214921502151215221532154215521562157215821592160216121622163216421652166216721682169217021712172217321742175217621772178217921802181218221832184218521862187218821892190219121922193219421952196219721982199220022012202220322042205220622072208220922102211221222132214221522162217221822192220222122222223222422252226222722282229223022312232223322342235223622372238223922402241224222432244224522462247224822492250225122522253225422552256225722582259226022612262226322642265226622672268226922702271227222732274227522762277227822792280228122822283228422852286228722882289229022912292229322942295229622972298229923002301230223032304230523062307230823092310231123122313231423152316231723182319232023212322232323242325232623272328232923302331233223332334233523362337 |
- Smalltalk createPackage: 'Kernel-Collections'!
- Object subclass: #Association
- instanceVariableNames: 'key value'
- package: 'Kernel-Collections'!
- !Association commentStamp!
- I represent a pair of associated objects, a key and a value. My instances can serve as entries in a dictionary.
- Instances can be created with the class-side method `#key:value:`!
- !Association methodsFor: 'accessing'!
- key
- ^ key
- !
- key: aKey
- key := aKey
- !
- value
- ^ value
- !
- value: aValue
- value := aValue
- ! !
- !Association methodsFor: 'comparing'!
- = anAssociation
- ^ self class = anAssociation class and: [
- self key = anAssociation key and: [
- self value = anAssociation value ]]
- ! !
- !Association methodsFor: 'printing'!
- printOn: aStream
- self key printOn: aStream.
- aStream nextPutAll: ' -> '.
- self value printOn: aStream
- ! !
- !Association class methodsFor: 'instance creation'!
- key: aKey value: aValue
- ^ self new
- key: aKey;
- value: aValue;
- yourself
- ! !
- Object subclass: #BucketStore
- instanceVariableNames: 'buckets hashBlock'
- package: 'Kernel-Collections'!
- !BucketStore commentStamp!
- I am an helper class for hash-based stores.
- I hold buckets which are selected by a hash, specified using `#hashBlock:`.
- The hash can be any object, and
- it is used as a JS property (that is, in ES5
- its toString() value counts).
- ## API
- I maintain a list of buckets. Client code can use this API:
- - `#bucketOfElement:` (to ask a bucket for element, I can return JS null if n/a)
- - `#do:` (to enumerate all elements of all buckets)
- - `#removeAll` (to remove all buckets)
- Client code itself should add/remove elements
- in a bucket. The `nil` object should not be put into any bucket.
- Types of buckets are the responsibility of subclasses via `#newBucket`.!
- !BucketStore methodsFor: 'accessing'!
- bucketOfElement: anObject
- <
- var hash = self['@hashBlock'](anObject);
- if (!!hash) return null;
- var buckets = self['@buckets'],
- bucket = buckets[hash];
- if (!!bucket) { bucket = buckets[hash] = self._newBucket(); }
- return bucket;
- >
- !
- hashBlock: aBlock
- hashBlock := aBlock
- ! !
- !BucketStore methodsFor: 'adding/removing'!
- removeAll
- <self['@buckets'] = Object.create(null);>
- ! !
- !BucketStore methodsFor: 'enumerating'!
- do: aBlock
- <
- var buckets = self['@buckets'];
- var keys = Object.keys(buckets);
- for (var i = 0; i < keys.length; ++i) { buckets[keys[i]]._do_(aBlock); }
- >
- ! !
- !BucketStore methodsFor: 'initialization'!
- initialize
- super initialize.
- self removeAll
- ! !
- !BucketStore methodsFor: 'private'!
- newBucket
- self subclassResponsibility
- ! !
- !BucketStore class methodsFor: 'instance creation'!
- hashBlock: aBlock
- ^ self new
- hashBlock: aBlock;
- yourself
- ! !
- BucketStore subclass: #ArrayBucketStore
- instanceVariableNames: ''
- package: 'Kernel-Collections'!
- !ArrayBucketStore commentStamp!
- I am a concrete `BucketStore` with buckets being instance of `Array`.!
- !ArrayBucketStore methodsFor: 'private'!
- newBucket
- ^ #()
- ! !
- Object subclass: #Collection
- instanceVariableNames: ''
- package: 'Kernel-Collections'!
- !Collection commentStamp!
- I am the abstract superclass of all classes that represent a group of elements.
- I provide a set of useful methods to the Collection hierarchy such as enumerating and converting methods.!
- !Collection methodsFor: 'accessing'!
- occurrencesOf: anObject
- "Answer how many of the receiver's elements are equal to anObject."
- | tally |
- tally := 0.
- self do: [ :each | anObject = each ifTrue: [ tally := tally + 1 ]].
- ^ tally
- !
- size
- self subclassResponsibility
- ! !
- !Collection methodsFor: 'adding/removing'!
- add: anObject
- self subclassResponsibility
- !
- addAll: aCollection
- aCollection do: [ :each |
- self add: each ].
- ^ aCollection
- !
- anyOne
- "Answer a representative sample of the receiver. This method can
- be helpful when needing to preinfer the nature of the contents of
- semi-homogeneous collections."
- self ifEmpty: [ self error: 'Collection is empty' ].
- self do: [ :each | ^ each ]
- !
- remove: anObject
- ^ self remove: anObject ifAbsent: [ self errorNotFound ]
- !
- remove: anObject ifAbsent: aBlock
- self subclassResponsibility
- !
- removeAll
- self subclassResponsibility
- ! !
- !Collection methodsFor: 'converting'!
- asArray
- ^ Array withAll: self
- !
- asJSON
- ^ self asArray collect: [ :each | each asJSON ]
- !
- asOrderedCollection
- ^ self asArray
- !
- asSet
- ^ Set withAll: self
- ! !
- !Collection methodsFor: 'copying'!
- , aCollection
- ^ self copy
- addAll: aCollection;
- yourself
- !
- copyWith: anObject
- ^ self copy add: anObject; yourself
- !
- copyWithAll: aCollection
- ^ self copy addAll: aCollection; yourself
- !
- copyWithoutAll: aCollection
- "Answer a copy of the receiver that does not contain any elements
- equal to those in aCollection."
- ^ self reject: [ :each | aCollection includes: each ]
- ! !
- !Collection methodsFor: 'enumerating'!
- allSatisfy: aBlock
- "Evaluate aBlock with the elements of the receiver.
- If aBlock returns false for any element return false.
- Otherwise return true."
- self do: [ :each | (aBlock value: each) ifFalse: [ ^ false ] ].
- ^ true
- !
- anySatisfy: aBlock
- "Evaluate aBlock with the elements of the receiver.
- If aBlock returns true for any element return true.
- Otherwise return false."
- self do: [ :each | (aBlock value: each) ifTrue: [ ^ true ] ].
- ^ false
- !
- collect: aBlock
- | stream |
- stream := self class new writeStream.
- self do: [ :each |
- stream nextPut: (aBlock value: each) ].
- ^ stream contents
- !
- detect: aBlock
- ^ self detect: aBlock ifNone: [ self errorNotFound ]
- !
- detect: aBlock ifNone: anotherBlock
- self subclassResponsibility
- !
- do: aBlock
- self subclassResponsibility
- !
- do: aBlock separatedBy: anotherBlock
- | actionBeforeElement |
- actionBeforeElement := [ actionBeforeElement := anotherBlock ].
- self do: [ :each |
- actionBeforeElement value.
- aBlock value: each ]
- !
- inject: anObject into: aBlock
- | result |
- result := anObject.
- self do: [ :each |
- result := aBlock value: result value: each ].
- ^ result
- !
- intersection: aCollection
- "Answer the set theoretic intersection of two collections."
- | set outputSet |
-
- set := self asSet.
- outputSet := Set new.
-
- aCollection do: [ :each |
- ((set includes: each) and: [ (outputSet includes: each) not ])
- ifTrue: [
- outputSet add: each ]].
-
- ^ self class withAll: outputSet asArray
- !
- noneSatisfy: aBlock
- "Evaluate aBlock with the elements of the receiver.
- If aBlock returns false for all elements return true.
- Otherwise return false"
- self do: [ :item | (aBlock value: item) ifTrue: [ ^ false ] ].
- ^ true
- !
- reject: aBlock
- ^ self select: [ :each | (aBlock value: each) = false ]
- !
- select: aBlock
- | stream |
- stream := self class new writeStream.
- self do: [ :each |
- (aBlock value: each) ifTrue: [
- stream nextPut: each ] ].
- ^ stream contents
- !
- select: selectBlock thenCollect: collectBlock
- | stream |
- stream := self class new writeStream.
- self do: [ :each |
- (selectBlock value: each) ifTrue: [
- stream nextPut: (collectBlock value: each) ] ].
- ^ stream contents
- ! !
- !Collection methodsFor: 'error handling'!
- errorNotFound
- self error: 'Object is not in the collection'
- ! !
- !Collection methodsFor: 'streaming'!
- putOn: aStream
- self do: [ :each | each putOn: aStream ]
- ! !
- !Collection methodsFor: 'testing'!
- contains: aBlock
- self deprecatedAPI.
- ^ self anySatisfy: aBlock
- !
- ifEmpty: aBlock
- "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:
- (myProtocol ifEmpty: ['As yet unclassified'])"
- ^ self isEmpty
- ifTrue: aBlock
- ifFalse: [ self ]
- !
- ifEmpty: aBlock ifNotEmpty: anotherBlock
- ^ self isEmpty
- ifTrue: aBlock
- ifFalse: [ anotherBlock value: self ]
- !
- ifNotEmpty: aBlock
- ^ self notEmpty
- ifTrue: [ aBlock value: self ]
- ifFalse: [ self ]
- !
- ifNotEmpty: aBlock ifEmpty: anotherBlock
- ^ self notEmpty
- ifTrue: [ aBlock value: self ]
- ifFalse: anotherBlock
- !
- includes: anObject
- ^ self anySatisfy: [ :each | each = anObject ]
- !
- isEmpty
- ^ self size = 0
- !
- notEmpty
- ^ self isEmpty not
- ! !
- !Collection class methodsFor: 'helios'!
- heliosClass
- ^ 'collection'
- ! !
- !Collection class methodsFor: 'instance creation'!
- new: anInteger
- ^ self new
- !
- with: anObject
- ^ self new
- add: anObject;
- yourself
- !
- with: anObject with: anotherObject
- ^ self new
- add: anObject;
- add: anotherObject;
- yourself
- !
- with: firstObject with: secondObject with: thirdObject
- ^ self new
- add: firstObject;
- add: secondObject;
- add: thirdObject;
- yourself
- !
- withAll: aCollection
- ^ self new
- addAll: aCollection;
- yourself
- ! !
- Collection subclass: #IndexableCollection
- instanceVariableNames: ''
- package: 'Kernel-Collections'!
- !IndexableCollection commentStamp!
- I am a key-value store collection, that is,
- I store values under indexes.
- As a rule of thumb, if a collection has `#at:` and `#at:put:`,
- it is an IndexableCollection.!
- !IndexableCollection methodsFor: 'accessing'!
- at: anIndex
- "Lookup the given index in the receiver.
- If it is present, answer the value stored at anIndex.
- Otherwise, raise an error."
- ^ self at: anIndex ifAbsent: [ self errorNotFound ]
- !
- at: anIndex ifAbsent: aBlock
- "Lookup the given index in the receiver.
- If it is present, answer the value stored at anIndex.
- Otherwise, answer the value of aBlock."
- self subclassResponsibility
- !
- at: aKey ifAbsentPut: aBlock
- ^ self at: aKey ifAbsent: [
- self at: aKey put: aBlock value ]
- !
- at: anIndex ifPresent: aBlock
- "Lookup the given index in the receiver.
- If it is present, answer the value of evaluating aBlock with the value stored at anIndex.
- Otherwise, answer nil."
- ^ self at: anIndex ifPresent: aBlock ifAbsent: [ nil ]
- !
- at: anIndex ifPresent: aBlock ifAbsent: anotherBlock
- "Lookup the given index in the receiver.
- If it is present, answer the value of evaluating aBlock with the value stored at anIndex.
- Otherwise, answer the value of anotherBlock."
- self subclassResponsibility
- !
- at: anIndex put: anObject
- "Store anObject under the given index in the receiver."
- self subclassResponsibility
- !
- indexOf: anObject
- "Lookup index at which anObject is stored in the receiver.
- If not present, raise an error."
- ^ self indexOf: anObject ifAbsent: [ self errorNotFound ]
- !
- indexOf: anObject ifAbsent: aBlock
- "Lookup index at which anObject is stored in the receiver.
- If not present, return value of executing aBlock."
- self subclassResponsibility
- ! !
- !IndexableCollection methodsFor: 'enumerating'!
- with: anotherCollection do: aBlock
- "Calls aBlock with every value from self
- and with indetically-indexed value from anotherCollection"
- self withIndexDo: [ :each :index |
- aBlock value: each value: (anotherCollection at: index) ]
- !
- withIndexDo: aBlock
- "Calls aBlock with every value from self
- and with its index as the second argument"
- self subclassResponsibility
- ! !
- IndexableCollection subclass: #AssociativeCollection
- instanceVariableNames: ''
- package: 'Kernel-Collections'!
- !AssociativeCollection commentStamp!
- I am a base class for object-indexed collections (Dictionary et.al.).!
- !AssociativeCollection methodsFor: 'accessing'!
- associations
- | associations |
- associations := #().
- self associationsDo: [ :each | associations add: each ].
- ^ associations
- !
- at: aKey ifPresent: aBlock ifAbsent: anotherBlock
- "Lookup the given key in the receiver.
- If it is present, answer the value of evaluating the oneArgBlock
- with the value associated with the key, otherwise answer the value
- of absentBlock."
-
- ^ (self includesKey: aKey)
- ifTrue: [ aBlock value: (self at: aKey) ]
- ifFalse: [ anotherBlock value ]
- !
- indexOf: anObject ifAbsent: aBlock
- ^ self keys
- detect: [ :each | (self at: each) = anObject ]
- ifNone: aBlock
- !
- keyAtValue: anObject
- ^ self keyAtValue: anObject ifAbsent: [ self errorNotFound ]
- !
- keyAtValue: anObject ifAbsent: aBlock
- ^ self indexOf: anObject ifAbsent: aBlock
- !
- keys
- self subclassResponsibility
- !
- size
- ^ self keys size
- !
- values
- self subclassResponsibility
- ! !
- !AssociativeCollection methodsFor: 'adding/removing'!
- add: anAssociation
- self at: anAssociation key put: anAssociation value
- !
- addAll: anAssociativeCollection
- super addAll: anAssociativeCollection associations.
- ^ anAssociativeCollection
- !
- remove: aKey ifAbsent: aBlock
- ^ self removeKey: aKey ifAbsent: aBlock
- !
- removeAll
- ^ self keys do: [ :each | self removeKey: each ]
- !
- removeKey: aKey
- ^ self remove: aKey
- !
- removeKey: aKey ifAbsent: aBlock
- self subclassResponsibility
- ! !
- !AssociativeCollection methodsFor: 'comparing'!
- = anAssocitativeCollection
- self class = anAssocitativeCollection class ifFalse: [ ^ false ].
- self size = anAssocitativeCollection size ifFalse: [ ^ false ].
- ^ self associations = anAssocitativeCollection associations
- ! !
- !AssociativeCollection methodsFor: 'converting'!
- asDictionary
- ^ Dictionary from: self associations
- !
- asHashedCollection
- ^ HashedCollection from: self associations
- !
- asJSON
- | hash |
- hash := HashedCollection new.
- self keysAndValuesDo: [ :key :value |
- hash at: key put: value asJSON ].
- ^ hash
- ! !
- !AssociativeCollection methodsFor: 'copying'!
- deepCopy
- | copy |
- copy := self class new.
- self keysAndValuesDo: [ :key :value |
- copy at: key put: value deepCopy ].
- ^ copy
- !
- shallowCopy
- | copy |
- copy := self class new.
- self keysAndValuesDo: [ :key :value |
- copy at: key put: value ].
- ^ copy
- ! !
- !AssociativeCollection methodsFor: 'enumerating'!
- associationsDo: aBlock
- self keysAndValuesDo: [ :key :value |
- aBlock value: (Association key: key value: value) ]
- !
- collect: aBlock
- | newDict |
- newDict := self class new.
- self keysAndValuesDo: [ :key :value |
- newDict at: key put: (aBlock value: value) ].
- ^ newDict
- !
- detect: aBlock ifNone: anotherBlock
- ^ self values detect: aBlock ifNone: anotherBlock
- !
- do: aBlock
- self valuesDo: aBlock
- !
- includes: anObject
- ^ self values includes: anObject
- !
- keysAndValuesDo: aBlock
- self keysDo: [ :each |
- aBlock value: each value: (self at: each) ]
- !
- keysDo: aBlock
- self subclassResponsibility
- !
- select: aBlock
- | newDict |
- newDict := self class new.
- self keysAndValuesDo: [ :key :value |
- (aBlock value: value) ifTrue: [ newDict at: key put: value ]].
- ^ newDict
- !
- valuesDo: aBlock
- self subclassResponsibility
- !
- withIndexDo: aBlock
- self keysAndValuesDo: [ :key :value | aBlock value: value value: key ]
- ! !
- !AssociativeCollection methodsFor: 'printing'!
- printOn: aStream
- super printOn: aStream.
-
- aStream nextPutAll: ' ('.
- self associations
- do: [ :each | each printOn: aStream ]
- separatedBy: [ aStream nextPutAll: ' , ' ].
- aStream nextPutAll: ')'
- ! !
- !AssociativeCollection methodsFor: 'testing'!
- includesKey: aKey
- self subclassResponsibility
- ! !
- !AssociativeCollection class methodsFor: 'instance creation'!
- from: aCollection
- | newCollection |
- newCollection := self new.
- aCollection do: [ :each | newCollection add: each ].
- ^ newCollection
- !
- fromPairs: aCollection
- "This message is poorly named and has been replaced by #from:"
- ^ self from: aCollection
- !
- newFromPairs: aCollection
- "Accept an array of elements where every two elements form an
- association - the odd element being the key, and the even element the value."
-
- | newCollection |
-
- aCollection size even ifFalse: [
- self error: '#newFromPairs only accepts arrays of an even length' ].
-
- newCollection := self new.
- ( 1 to: aCollection size by: 2 ) do: [ :each |
- newCollection at: (aCollection at: each) put: (aCollection at: each + 1) ].
-
- ^ newCollection
- ! !
- AssociativeCollection subclass: #Dictionary
- instanceVariableNames: 'keys values'
- package: 'Kernel-Collections'!
- !Dictionary commentStamp!
- I represent a set of elements that can be viewed from one of two perspectives: a set of associations,
- or a container of values that are externally named where the name can be any object that responds to `=`.
- The external name is referred to as the key.!
- !Dictionary methodsFor: 'accessing'!
- at: aKey ifAbsent: aBlock
- <
- var index = self._positionOfKey_(aKey);
- return index >>=0 ? self['@values'][index] : aBlock._value();
- >
- !
- at: aKey put: aValue
- <
- var index = self._positionOfKey_(aKey);
- if(index === -1) {
- var keys = self['@keys'];
- index = keys.length;
- keys.push(aKey);
- }
- return self['@values'][index] = aValue;
- >
- !
- indexOf: anObject ifAbsent: aBlock
- | index |
- index := values
- indexOf: anObject
- ifAbsent: [ 0 ].
- ^ index = 0
- ifTrue: [ aBlock value ]
- ifFalse: [ keys at: index ]
- !
- keys
- ^ keys copy
- !
- values
- ^ values
- ! !
- !Dictionary methodsFor: 'adding/removing'!
- removeAll
- keys removeAll.
- values removeAll
- !
- removeKey: aKey ifAbsent: aBlock
- <
- var index = self._positionOfKey_(aKey);
- if(index === -1) {
- return aBlock._value()
- } else {
- var keys = self['@keys'], values = self['@values'];
- var value = values[index], l = keys.length;
- keys[index] = keys[l-1];
- keys.pop();
- values[index] = values[l-1];
- values.pop();
- return value;
- }
- >
- ! !
- !Dictionary methodsFor: 'enumerating'!
- keysAndValuesDo: aBlock
- ^ keys with: values do: aBlock
- !
- keysDo: aBlock
- ^ keys do: aBlock
- !
- valuesDo: aBlock
- ^ values do: aBlock
- ! !
- !Dictionary methodsFor: 'initialization'!
- initialize
- super initialize.
- keys := #().
- values := #()
- ! !
- !Dictionary methodsFor: 'private'!
- positionOfKey: anObject
- <
- var keys = self['@keys'];
- for(var i=0;i<keys.length;i++){
- if(keys[i].__eq(anObject)) { return i;}
- }
- return -1;
- >
- ! !
- !Dictionary methodsFor: 'testing'!
- includesKey: aKey
- < return self._positionOfKey_(aKey) >>= 0; >
- ! !
- AssociativeCollection subclass: #HashedCollection
- instanceVariableNames: ''
- package: 'Kernel-Collections'!
- !HashedCollection commentStamp!
- I am a traditional JavaScript object, or a Smalltalk `Dictionary`.
- Unlike a `Dictionary`, I can only have strings as keys.!
- !HashedCollection methodsFor: 'accessing'!
- at: aKey ifAbsent: aBlock
- ^ (self includesKey: aKey)
- ifTrue: [ self basicAt: aKey ]
- ifFalse: [ aBlock value ]
- !
- at: aKey put: aValue
- ^ self basicAt: aKey put: aValue
- !
- keys
- <return Object.keys(self)>
- !
- values
- <
- return self._keys().map(function(key){
- return self._at_(key);
- });
- >
- ! !
- !HashedCollection methodsFor: 'adding/removing'!
- removeKey: aKey ifAbsent: aBlock
- ^ self
- at: aKey
- ifPresent: [ :removed | self basicDelete: aKey. removed ]
- ifAbsent: [ aBlock value ]
- ! !
- !HashedCollection methodsFor: 'enumerating'!
- keysDo: aBlock
- self keys do: aBlock
- !
- valuesDo: aBlock
- self values do: aBlock
- ! !
- !HashedCollection methodsFor: 'testing'!
- includesKey: aKey
- <return self.hasOwnProperty(aKey)>
- ! !
- IndexableCollection subclass: #SequenceableCollection
- instanceVariableNames: ''
- package: 'Kernel-Collections'!
- !SequenceableCollection commentStamp!
- I am an IndexableCollection
- with numeric indexes starting with 1.!
- !SequenceableCollection methodsFor: 'accessing'!
- allButFirst
- ^ self copyFrom: 2 to: self size
- !
- allButLast
- ^ self copyFrom: 1 to: self size - 1
- !
- atRandom
- ^ self at: self size atRandom
- !
- first
- ^ self at: 1
- !
- first: aNumber
- "Answer the first `aNumber` elements of the receiver.
- Raise an error if there are not enough elements in the receiver."
- self size < aNumber ifTrue: [ self error: 'Invalid number of elements' ].
- ^ self copyFrom: 1 to: aNumber
- !
- fourth
- ^ self at: 4
- !
- indexOf: anObject ifAbsent: aBlock
- <
- self = self._numericallyIndexable();
- for(var i=0; i < self.length; i++) {
- if($recv(self[i]).__eq(anObject)) {return i+1}
- };
- return aBlock._value();
- >
- !
- indexOf: anObject startingAt: start
- "Answer the index of the first occurence of anElement after start
- within the receiver. If the receiver does not contain anElement,
- answer 0."
- ^ self indexOf: anObject startingAt: start ifAbsent: [ 0 ]
- !
- indexOf: anObject startingAt: start ifAbsent: aBlock
- <
- self = self._numericallyIndexable();
- for(var i=start - 1; i < self.length; i++){
- if($recv(self[i]).__eq(anObject)) {return i+1}
- }
- return aBlock._value();
- >
- !
- last
- ^ self at: self size
- !
- last: aNumber
- "Answer the last aNumber elements of the receiver.
- Raise an error if there are not enough elements in the receiver."
- self size < aNumber ifTrue: [ self error: 'Invalid number of elements' ].
- ^ self copyFrom: self size - aNumber + 1 to: self size
- !
- second
- ^ self at: 2
- !
- third
- ^ self at: 3
- ! !
- !SequenceableCollection methodsFor: 'adding/removing'!
- addLast: anObject
- self add: anObject
- !
- removeLast
- ^ self remove: self last
- ! !
- !SequenceableCollection methodsFor: 'comparing'!
- = aCollection
- (self class = aCollection class and: [
- self size = aCollection size ]) ifFalse: [ ^ false ].
- self withIndexDo: [ :each :i |
- (aCollection at: i) = each ifFalse: [ ^ false ]].
- ^ true
- ! !
- !SequenceableCollection methodsFor: 'converting'!
- reversed
- self subclassResponsibility
- ! !
- !SequenceableCollection methodsFor: 'copying'!
- copyFrom: anIndex to: anotherIndex
- | range newCollection |
- range := anIndex to: anotherIndex.
- newCollection := self class new: range size.
- range withIndexDo: [ :each :i |
- newCollection at: i put: (self at: each) ].
- ^ newCollection
- !
- deepCopy
- | newCollection |
- newCollection := self class new: self size.
- self withIndexDo: [ :each :index |
- newCollection at: index put: each deepCopy ].
- ^ newCollection
- !
- shallowCopy
- | newCollection |
- newCollection := self class new: self size.
- self withIndexDo: [ :each :index |
- newCollection at: index put: each ].
- ^ newCollection
- ! !
- !SequenceableCollection methodsFor: 'enumerating'!
- detect: aBlock ifNone: anotherBlock
- <
- self = self._numericallyIndexable();
- for(var i = 0; i < self.length; i++)
- if(aBlock._value_(self[i]))
- return self[i];
- return anotherBlock._value();
- >
- !
- do: aBlock
- <
- self = self._numericallyIndexable();
- for(var i=0; i < self.length; i++) {
- aBlock._value_(self[i]);
- }
- >
- !
- with: anotherCollection do: aBlock
- <
- self = self._numericallyIndexable();
- anotherCollection = anotherCollection._numericallyIndexable();
- for(var i=0; i<self.length; i++) {
- aBlock._value_value_(self[i], anotherCollection[i]);
- }
- >
- !
- withIndexDo: aBlock
- <
- self = self._numericallyIndexable();
- for(var i=0; i < self.length; i++) {
- aBlock._value_value_(self[i], i+1);
- }
- >
- ! !
- !SequenceableCollection methodsFor: 'private'!
- numericallyIndexable
- "This is an internal converting message.
- It answeres a representation of the receiver
- that can use foo[i] in JavaScript code.
-
- It fixes IE8, where boxed String is unable
- to numerically index its characters,
- but primitive string can."
-
- self subclassResponsibility
- ! !
- !SequenceableCollection methodsFor: 'streaming'!
- newStream
- ^ self streamClass on: self
- !
- readStream
- "For Pharo compatibility"
-
- ^ self stream
- !
- stream
- ^ self newStream
- !
- streamClass
- ^ self class streamClass
- !
- writeStream
- "For Pharo compatibility"
-
- ^ self stream
- ! !
- !SequenceableCollection methodsFor: 'testing'!
- beginsWith: prefix
- self size < prefix size ifTrue: [ ^ false ].
- ^ (self first: prefix size) = prefix
- !
- endsWith: suffix
- self size < suffix size ifTrue: [ ^ false ].
- ^ (self last: suffix size) = suffix
- !
- includes: anObject
- ^ (self indexOf: anObject ifAbsent: [ nil ]) notNil
- ! !
- !SequenceableCollection class methodsFor: 'accessing'!
- streamClass
- ^ Stream
- ! !
- !SequenceableCollection class methodsFor: 'streaming'!
- streamContents: aBlock
- | stream |
- stream := (self streamClass on: self new).
- aBlock value: stream.
- ^ stream contents
- ! !
- SequenceableCollection subclass: #Array
- instanceVariableNames: ''
- package: 'Kernel-Collections'!
- !Array commentStamp!
- I represent a collection of objects ordered by the collector. The size of arrays is dynamic.
- I am directly mapped to JavaScript Number.
- *Note* In Amber, `OrderedCollection` is an alias for `Array`.!
- !Array methodsFor: 'accessing'!
- at: anIndex ifAbsent: aBlock
- <
- return anIndex >>= 1 && anIndex <= self.length
- ? self[anIndex - 1]
- : aBlock._value()
- >
- !
- at: anIndex ifPresent: aBlock ifAbsent: anotherBlock
- <
- return anIndex >>= 1 && anIndex <= self.length
- ? aBlock._value_(self[anIndex - 1])
- : anotherBlock._value()
- >
- !
- at: anIndex put: anObject
- <return self[anIndex - 1] = anObject>
- !
- size
- <return self.length>
- ! !
- !Array methodsFor: 'adding/removing'!
- add: anObject
- <self.push(anObject); return anObject;>
- !
- addFirst: anObject
- <self.unshift(anObject); return anObject;>
- !
- remove: anObject ifAbsent: aBlock
- | index |
- index := self indexOf: anObject ifAbsent: [ 0 ].
- ^ index = 0
- ifFalse: [ self removeIndex: index. anObject ]
- ifTrue: [ aBlock value ]
- !
- removeAll
- <self.length = 0>
- !
- removeFrom: aNumber to: anotherNumber
- <self.splice(aNumber -1, anotherNumber - aNumber + 1)>
- !
- removeIndex: anInteger
- <self.splice(anInteger - 1, 1)>
- !
- removeLast
- <return self.pop();>
- ! !
- !Array methodsFor: 'converting'!
- asJavascript
- ^ '[', ((self collect: [:each | each asJavascript ]) join: ', '), ']'
- !
- reversed
- <return self._copy().reverse()>
- ! !
- !Array methodsFor: 'enumerating'!
- collect: aBlock
- "Optimized version"
-
- <return self.map(function(each) {return aBlock._value_(each)})>
- !
- join: aString
- <return self.join(aString)>
- !
- select: aBlock
- "Optimized version"
-
- <
- var result = self.klass._new();
- for(var i=0; i<self.length; i++) {
- if(aBlock._value_(self[i])) {
- result.push(self[i]);
- }
- }
- return result;
- >
- !
- sort
- ^ self sort: [ :a :b | a < b ]
- !
- sort: aBlock
- <
- return self.sort(function(a, b) {
- if(aBlock._value_value_(a,b)) {return -1} else {return 1}
- })
- >
- !
- sorted
- ^ self copy sort
- !
- sorted: aBlock
- ^ self copy sort: aBlock
- ! !
- !Array methodsFor: 'printing'!
- printOn: aStream
- super printOn: aStream.
-
- aStream nextPutAll: ' ('.
- self
- do: [ :each | each printOn: aStream ]
- separatedBy: [ aStream nextPutAll: ' ' ].
- aStream nextPutAll: ')'
- ! !
- !Array methodsFor: 'private'!
- numericallyIndexable
- ^ self
- ! !
- !Array class methodsFor: 'instance creation'!
- new: anInteger
- <return new Array(anInteger)>
- !
- with: anObject
- ^ (self new: 1)
- at: 1 put: anObject;
- yourself
- !
- with: anObject with: anObject2
- ^ (self new: 2)
- at: 1 put: anObject;
- at: 2 put: anObject2;
- yourself
- !
- with: anObject with: anObject2 with: anObject3
- ^ (self new: 3)
- at: 1 put: anObject;
- at: 2 put: anObject2;
- at: 3 put: anObject3;
- yourself
- !
- withAll: aCollection
- | instance index |
- index := 1.
- instance := self new: aCollection size.
- aCollection do: [ :each |
- instance at: index put: each.
- index := index + 1 ].
- ^ instance
- ! !
- SequenceableCollection subclass: #CharacterArray
- instanceVariableNames: ''
- package: 'Kernel-Collections'!
- !CharacterArray commentStamp!
- I am the abstract superclass of string-like collections.!
- !CharacterArray methodsFor: 'accessing'!
- at: anIndex put: anObject
- self errorReadOnly
- ! !
- !CharacterArray methodsFor: 'adding/removing'!
- add: anObject
- self errorReadOnly
- !
- remove: anObject
- self errorReadOnly
- ! !
- !CharacterArray methodsFor: 'converting'!
- asLowercase
- ^ self class fromString: self asString asLowercase
- !
- asNumber
- ^ self asString asNumber
- !
- asString
- ^ self subclassResponsibility
- !
- asSymbol
- ^ self asString
- !
- asUppercase
- ^ self class fromString: self asString asUppercase
- ! !
- !CharacterArray methodsFor: 'copying'!
- , aString
- ^ self asString, aString asString
- ! !
- !CharacterArray methodsFor: 'error handling'!
- errorReadOnly
- self error: 'Object is read-only'
- ! !
- !CharacterArray methodsFor: 'printing'!
- printOn: aStream
- self asString printOn: aStream
- ! !
- !CharacterArray methodsFor: 'streaming'!
- putOn: aStream
- aStream nextPutString: self
- ! !
- !CharacterArray class methodsFor: 'instance creation'!
- fromString: aString
- self subclassResponsibility
- ! !
- CharacterArray subclass: #String
- instanceVariableNames: ''
- package: 'Kernel-Collections'!
- !String commentStamp!
- 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.
- String inherits many useful methods from its hierarchy, such as
- `Collection >> #,`!
- !String methodsFor: 'accessing'!
- asciiValue
- <return self.charCodeAt(0);>
- !
- at: anIndex ifAbsent: aBlock
- <return String(self)[anIndex - 1] || aBlock._value()>
- !
- at: anIndex ifPresent: aBlock ifAbsent: anotherBlock
- <
- var result = String(self)[anIndex - 1];
- return result ? aBlock._value_(result) : anotherBlock._value();
- >
- !
- charCodeAt: anInteger
- <return self.charCodeAt(anInteger - 1)>
- !
- identityHash
- ^ self, 's'
- !
- size
- <return self.length>
- ! !
- !String methodsFor: 'comparing'!
- < aString
- <return String(self) < aString._asString()>
- !
- <= aString
- <return String(self) <= aString._asString()>
- !
- = aString
- <
- return aString !!= null &&
- typeof aString._isString === "function" &&
- aString._isString() &&
- String(self) === String(aString)
- >
- !
- == aString
- ^ self = aString
- !
- > aString
- <return String(self) >> aString._asString()>
- !
- >= aString
- <return String(self) >>= aString._asString()>
- ! !
- !String methodsFor: 'converting'!
- asJSON
- ^ self
- !
- asJavaScriptMethodName
- <return $core.st2js(self)>
- !
- asJavascript
- <
- if(self.search(/^[a-zA-Z0-9_:.$ ]*$/) == -1)
- return "\"" + self.replace(/[\x00-\x1f"\\\x7f-\x9f]/g, function(ch){var c=ch.charCodeAt(0);return "\\x"+("0"+c.toString(16)).slice(-2)}) + "\"";
- else
- return "\"" + self + "\"";
- >
- !
- asLowercase
- <return self.toLowerCase()>
- !
- asMutator
- "Answer a setter selector. For example,
- #name asMutator returns #name:"
- self last = ':' ifFalse: [ ^ self, ':' ].
- ^ self
- !
- asNumber
- <return Number(self)>
- !
- asRegexp
- ^ RegularExpression fromString: self
- !
- asSelector
- self deprecatedAPI: 'Use #asJavaScriptMethodName'.
- ^ self asJavaScriptMethodName
- !
- asString
- ^ self
- !
- asSymbol
- ^ self
- !
- asUppercase
- <return self.toUpperCase()>
- !
- capitalized
- ^ self isEmpty
- ifTrue: [ self ]
- ifFalse: [ self first asUppercase, self allButFirst ]
- !
- crlfSanitized
- ^ self lines join: String lf
- !
- escaped
- <return escape(self)>
- !
- reversed
- <return self.split("").reverse().join("")>
- !
- unescaped
- <return unescape(self)>
- !
- uriComponentDecoded
- <return decodeURIComponent(self)>
- !
- uriComponentEncoded
- <return encodeURIComponent(self)>
- !
- uriDecoded
- <return decodeURI(self)>
- !
- uriEncoded
- <return encodeURI(self)>
- ! !
- !String methodsFor: 'copying'!
- , aString
- <return String(self) + aString>
- !
- copyFrom: anIndex to: anotherIndex
- <return self.substring(anIndex - 1, anotherIndex)>
- !
- deepCopy
- ^ self shallowCopy
- !
- shallowCopy
- ^ self class fromString: self
- ! !
- !String methodsFor: 'evaluating'!
- value: anObject
- ^ anObject perform: self
- ! !
- !String methodsFor: 'printing'!
- printNl
- <console.log(self)>
- !
- printOn: aStream
- aStream
- nextPutAll: '''';
- nextPutAll: self;
- nextPutAll: ''''
- ! !
- !String methodsFor: 'private'!
- numericallyIndexable
- <return String(self)>
- ! !
- !String methodsFor: 'regular expressions'!
- match: aRegexp
- <return self.search(aRegexp) !!= -1>
- !
- matchesOf: aRegularExpression
- <return self.match(aRegularExpression)>
- !
- replace: aString with: anotherString
- ^ self replaceRegexp: (RegularExpression fromString: aString flag: 'g') with: anotherString
- !
- replaceRegexp: aRegexp with: aString
- <return self.replace(aRegexp, aString)>
- !
- trimBoth
- ^ self trimBoth: '\s'
- !
- trimBoth: separators
- ^ (self trimLeft: separators) trimRight: separators
- !
- trimLeft
- ^ self trimLeft: '\s'
- !
- trimLeft: separators
- ^ self replaceRegexp: (RegularExpression fromString: '^[', separators, ']+' flag: 'g') with: ''
- !
- trimRight
- ^ self trimRight: '\s'
- !
- trimRight: separators
- ^ self replaceRegexp: (RegularExpression fromString: '[', separators, ']+$' flag: 'g') with: ''
- ! !
- !String methodsFor: 'split join'!
- join: aCollection
- ^ String
- streamContents: [ :stream | aCollection
- do: [ :each | stream nextPutAll: each asString ]
- separatedBy: [ stream nextPutAll: self ]]
- !
- lineIndicesDo: aBlock
- "execute aBlock with 3 arguments for each line:
- - start index of line
- - end index of line without line delimiter
- - end index of line including line delimiter(s) CR, LF or CRLF"
-
- | cr lf start sz nextLF nextCR |
- start := 1.
- sz := self size.
- cr := String cr.
- nextCR := self indexOf: cr startingAt: 1.
- lf := String lf.
- nextLF := self indexOf: lf startingAt: 1.
- [ start <= sz ] whileTrue: [
- (nextLF = 0 and: [ nextCR = 0 ])
- ifTrue: [ "No more CR, nor LF, the string is over"
- aBlock value: start value: sz value: sz.
- ^ self ].
- (nextCR = 0 or: [ 0 < nextLF and: [ nextLF < nextCR ] ])
- ifTrue: [ "Found a LF"
- aBlock value: start value: nextLF - 1 value: nextLF.
- start := 1 + nextLF.
- nextLF := self indexOf: lf startingAt: start ]
- ifFalse: [ 1 + nextCR = nextLF
- ifTrue: [ "Found a CR-LF pair"
- aBlock value: start value: nextCR - 1 value: nextLF.
- start := 1 + nextLF.
- nextCR := self indexOf: cr startingAt: start.
- nextLF := self indexOf: lf startingAt: start ]
- ifFalse: [ "Found a CR"
- aBlock value: start value: nextCR - 1 value: nextCR.
- start := 1 + nextCR.
- nextCR := self indexOf: cr startingAt: start ] ]]
- !
- lineNumber: anIndex
- "Answer a string containing the characters in the given line number."
- | lineCount |
- lineCount := 0.
- self lineIndicesDo: [ :start :endWithoutDelimiters :end |
- (lineCount := lineCount + 1) = anIndex ifTrue: [ ^ self copyFrom: start to: endWithoutDelimiters ]].
- ^ nil
- !
- lines
- "Answer an array of lines composing this receiver without the line ending delimiters."
- | lines |
- lines := Array new.
- self linesDo: [ :aLine | lines add: aLine ].
- ^ lines
- !
- linesDo: aBlock
- "Execute aBlock with each line in this string. The terminating line
- delimiters CR, LF or CRLF pairs are not included in what is passed to aBlock"
- self lineIndicesDo: [ :start :endWithoutDelimiters :end |
- aBlock value: (self copyFrom: start to: endWithoutDelimiters) ]
- !
- subStrings: aString
- ^ self tokenize: aString
- !
- tokenize: aString
- <return self.split(aString)>
- ! !
- !String methodsFor: 'testing'!
- includesSubString: subString
- <return self.indexOf(subString) !!= -1>
- !
- isCapitalized
- ^ self first asUppercase == self first
- !
- isImmutable
- ^ true
- !
- isString
- ^ true
- !
- isVowel
- "Answer true if the receiver is a one character string containing a voyel"
-
- ^ self size = 1 and: [ 'aeiou' includes: self asLowercase ]
- ! !
- !String class methodsFor: 'accessing'!
- cr
- <return '\r'>
- !
- crlf
- <return '\r\n'>
- !
- esc
- ^ self fromCharCode: 27
- !
- lf
- <return '\n'>
- !
- space
- <return ' '>
- !
- streamClass
- ^ StringStream
- !
- tab
- <return '\t'>
- ! !
- !String class methodsFor: 'instance creation'!
- fromCharCode: anInteger
- <return String.fromCharCode(anInteger)>
- !
- fromString: aString
- <return String(aString)>
- !
- value: aUTFCharCode
- <return String.fromCharCode(aUTFCharCode);>
- ! !
- !String class methodsFor: 'random'!
- random
- "Returns random alphanumeric string beginning with letter"
- <return (Math.random()*(22/32)+(10/32)).toString(32).slice(2);>
- !
- randomNotIn: aString
- | result |
- [ result := self random. aString includesSubString: result ] whileTrue.
- ^ result
- ! !
- Collection subclass: #Set
- instanceVariableNames: 'defaultBucket slowBucketStores fastBuckets size'
- package: 'Kernel-Collections'!
- !Set commentStamp!
- I represent an unordered set of objects without duplicates.
- ## Implementation notes
- I put elements into different stores based on their type.
- The goal is to store some elements into native JS object property names to be fast.
- If an unboxed element has typeof 'string', 'boolean' or 'number', or an element is nil, null or undefined,
- I store it as a property name in an empty (== Object.create(null)) JS object, different for each type
- (for simplicity, nil/null/undefined is treated as one and included with the two booleans).
- If element happen to be an object, I try to store them in `ArrayBucketStore`. I have two of them by default,
- one hashed using the Smalltalk class name, the other one using the JS constructor name. It is possible to have more or less
- instances of `ArrayBucketStores`, see `#initializeSlowBucketStores`.
- As a last resort, if none of the `ArrayBucketStore` instances can find a suitable bucket, the `defaultBucket` is used,
- which is an `Array`.!
- !Set methodsFor: 'accessing'!
- size
- ^ size
- ! !
- !Set methodsFor: 'adding/removing'!
- add: anObject
- | bucket |
- bucket := self bucketsOfElement: anObject.
- ^ bucket second
- ifNil: [
- | object slowBucket |
- object := bucket first.
- slowBucket := bucket third.
- slowBucket
- indexOf: object
- ifAbsent: [
- slowBucket add: object.
- size := size + 1 ].
- object ]
- ifNotNil: [ :primitiveBucket |
- self
- add: bucket first
- in: primitiveBucket ]
- !
- remove: anObject ifAbsent: aBlock
- | bucket |
- bucket := self bucketsOfElement: anObject.
- ^ bucket second
- ifNil: [ bucket third remove: bucket first ifAbsent: [ ^aBlock value ]. size := size - 1 ]
- ifNotNil: [ :primitiveBucket | self remove: bucket first in: primitiveBucket ]
- !
- removeAll
- <
- self['@fastBuckets'] = {
- 'boolean': { store: Object.create(null), fn: function (x) { return {'true': true, 'false': false, 'null': null}[x]; } },
- 'number': { store: Object.create(null), fn: Number },
- 'string': { store: Object.create(null) }
- };
- self['@slowBucketStores'].forEach(function (x) { x._removeAll(); });
- self['@defaultBucket']._removeAll();
- self['@size'] = 0;
- >
- ! !
- !Set methodsFor: 'comparing'!
- = aCollection
- self class = aCollection class ifFalse: [ ^ false ].
- self size = aCollection size ifFalse: [ ^ false ].
- self do: [ :each | (aCollection includes: each) ifFalse: [ ^ false ] ].
- ^ true
- ! !
- !Set methodsFor: 'enumerating'!
- collect: aBlock
- | collection |
- collection := self class new.
- self do: [ :each | collection add: (aBlock value: each) ].
- ^ collection
- !
- detect: aBlock ifNone: anotherBlock
- self do: [ :each | (aBlock value: each) ifTrue: [ ^each ] ].
- ^ anotherBlock value
- !
- do: aBlock
- <
- var el, keys, i;
- el = self['@fastBuckets'];
- keys = Object.keys(el);
- for (i = 0; i < keys.length; ++i) {
- var fastBucket = el[keys[i]], fn = fastBucket.fn, store = Object.keys(fastBucket.store);
- if (fn) { for (var j = 0; j < store.length; ++j) { aBlock._value_(fn(store[j])); } }
- else { store._do_(aBlock); }
- }
- el = self['@slowBucketStores'];
- for (i = 0; i < el.length; ++i) { el[i]._do_(aBlock); }
- self['@defaultBucket']._do_(aBlock);
- >
- !
- select: aBlock
- | collection |
- collection := self class new.
- self do: [ :each |
- (aBlock value: each) ifTrue: [
- collection add: each ] ].
- ^ collection
- ! !
- !Set methodsFor: 'initialization'!
- initialize
- super initialize.
-
- defaultBucket := #().
- self
- initializeSlowBucketStores;
- removeAll
- !
- initializeSlowBucketStores
- slowBucketStores := {
- ArrayBucketStore hashBlock: [ :x | self classNameOf: x ].
- ArrayBucketStore hashBlock: [ :x | self jsConstructorNameOf: x ]
- }
- ! !
- !Set methodsFor: 'printing'!
- printOn: aStream
- super printOn: aStream.
-
- aStream nextPutAll: ' ('.
- self
- do: [ :each | each printOn: aStream ]
- separatedBy: [ aStream nextPutAll: ' ' ].
- aStream nextPutAll: ')'
- ! !
- !Set methodsFor: 'private'!
- add: anObject in: anotherObject
- <
- if (anObject in anotherObject.store) { return false; }
- self['@size']++;
- return anotherObject.store[anObject] = true;
- >
- !
- bucketsOfElement: anObject
- "Find the appropriate bucket for `anObject`.
- For optimization purposes, directly answer an array with:
- - the object to be store
- - the primitive bucket
- - the slow bucket"
-
- <
- var type, bucket, prim = anObject == null ? (anObject = nil) : anObject.valueOf();
- if ((type = typeof prim) === "object") {
- if (anObject !!== nil) {
- bucket = null;
- self['@slowBucketStores'].some(function (store) {
- return bucket = store._bucketOfElement_(anObject);
- });
- return [ anObject, null, bucket || self['@defaultBucket'] ];
- }
-
- // include nil to well-known objects under 'boolean' fastBucket
- prim = null;
- type = 'boolean';
- }
- return [ prim, self['@fastBuckets'][type] ];
- >
- !
- classNameOf: anObject
- "Answer the class name of `anObject`, or `undefined`
- if `anObject` is not an Smalltalk object"
-
- <return anObject.klass && anObject.klass.className>
- !
- includes: anObject in: anotherObject
- <return anObject in anotherObject.store>
- !
- jsConstructorNameOf: anObject
- <return anObject.constructor && anObject.constructor.name>
- !
- remove: anObject in: anotherObject
- <if (delete anotherObject.store[anObject]) self['@size']-->
- ! !
- !Set methodsFor: 'testing'!
- includes: anObject
- | bucket |
- bucket := self bucketsOfElement: anObject.
- ^ bucket second
- ifNil: [ bucket third includes: bucket first ]
- ifNotNil: [ :primitiveBucket | self includes: bucket first in: primitiveBucket ]
- ! !
- Object subclass: #Queue
- instanceVariableNames: 'read readIndex write'
- package: 'Kernel-Collections'!
- !Queue commentStamp!
- I am a one-sided queue.
- ## Usage
- Use `#nextPut:` to add items to the queue.
- Use `#next` or `#nextIfAbsent:` to get (and remove) the next item in the queue.
- ## Implementation notes
- A Queue uses two OrderedCollections inside,
- `read` is at the front, is not modified and only read using `readIndex`.
- `write` is at the back and is appended new items.
- When `read` is exhausted, `write` is promoted to `read` and new `write` is created.
- As a consequence, no data moving is done by me, write appending may do data moving
- when growing `write`, but this is left to engine to implement as good as it chooses to.!
- !Queue methodsFor: 'accessing'!
- next
- ^ self nextIfAbsent: [ self error: 'Cannot read from empty Queue.' ]
- !
- nextIfAbsent: aBlock
- | result |
- result := read at: readIndex ifAbsent: [
- write isEmpty ifTrue: [
- readIndex > 1 ifTrue: [ read := #(). readIndex := 1 ].
- ^ aBlock value ].
- read := write.
- readIndex := 1.
- write := OrderedCollection new.
- read first ].
- read at: readIndex put: nil.
- readIndex := readIndex + 1.
- ^ result
- !
- nextPut: anObject
- write add: anObject
- ! !
- !Queue methodsFor: 'initialization'!
- initialize
- super initialize.
- read := OrderedCollection new.
- write := OrderedCollection new.
- readIndex := 1
- ! !
- Object subclass: #RegularExpression
- instanceVariableNames: ''
- package: 'Kernel-Collections'!
- !RegularExpression commentStamp!
- I represent a regular expression object. My instances are JavaScript `RegExp` object.!
- !RegularExpression methodsFor: 'evaluating'!
- compile: aString
- <return self.compile(aString)>
- !
- exec: aString
- <return self.exec(aString) || nil>
- !
- test: aString
- <return self.test(aString)>
- ! !
- !RegularExpression class methodsFor: 'instance creation'!
- fromString: aString
- ^ self fromString: aString flag: ''
- !
- fromString: aString flag: anotherString
- <return new RegExp(aString, anotherString)>
- ! !
- Object subclass: #Stream
- instanceVariableNames: 'collection position streamSize'
- package: 'Kernel-Collections'!
- !Stream commentStamp!
- I represent an accessor for a sequence of objects. This sequence is referred to as my "contents".
- My instances are read/write streams to the contents sequence collection.!
- !Stream methodsFor: 'accessing'!
- collection
- ^ collection
- !
- contents
- ^ self collection
- copyFrom: 1
- to: self streamSize
- !
- position
- ^ position ifNil: [ position := 0 ]
- !
- position: anInteger
- position := anInteger
- !
- setCollection: aCollection
- collection := aCollection
- !
- setStreamSize: anInteger
- streamSize := anInteger
- !
- size
- ^ self streamSize
- !
- streamSize
- ^ streamSize
- ! !
- !Stream methodsFor: 'actions'!
- close
- !
- flush
- !
- reset
- self position: 0
- !
- resetContents
- self reset.
- self setStreamSize: 0
- ! !
- !Stream methodsFor: 'enumerating'!
- do: aBlock
- [ self atEnd ] whileFalse: [ aBlock value: self next ]
- ! !
- !Stream methodsFor: 'positioning'!
- setToEnd
- self position: self size
- !
- skip: anInteger
- self position: ((self position + anInteger) min: self size max: 0)
- ! !
- !Stream methodsFor: 'reading'!
- next
- ^ self atEnd
- ifTrue: [ nil ]
- ifFalse: [
- self position: self position + 1.
- collection at: self position ]
- !
- next: anInteger
- | tempCollection |
- tempCollection := self collection class new.
- anInteger timesRepeat: [
- self atEnd ifFalse: [
- tempCollection add: self next ]].
- ^ tempCollection
- !
- peek
- ^ self atEnd ifFalse: [
- self collection at: self position + 1 ]
- ! !
- !Stream methodsFor: 'testing'!
- atEnd
- ^ self position = self size
- !
- atStart
- ^ self position = 0
- !
- isEmpty
- ^ self size = 0
- ! !
- !Stream methodsFor: 'writing'!
- << anObject
- self write: anObject
- !
- nextPut: anObject
- self position: self position + 1.
- self collection at: self position put: anObject.
- self setStreamSize: (self streamSize max: self position)
- !
- nextPutAll: aCollection
- aCollection do: [ :each |
- self nextPut: each ]
- !
- nextPutString: aString
- self nextPut: aString
- !
- write: anObject
- anObject putOn: self
- ! !
- !Stream class methodsFor: 'instance creation'!
- on: aCollection
- ^ self new
- setCollection: aCollection;
- setStreamSize: aCollection size;
- yourself
- ! !
- Stream subclass: #StringStream
- instanceVariableNames: ''
- package: 'Kernel-Collections'!
- !StringStream commentStamp!
- I am a Stream specific to `String` objects.!
- !StringStream methodsFor: 'reading'!
- next: anInteger
- | tempCollection |
- tempCollection := self collection class new.
- anInteger timesRepeat: [
- self atEnd ifFalse: [
- tempCollection := tempCollection, self next ]].
- ^ tempCollection
- ! !
- !StringStream methodsFor: 'writing'!
- cr
- ^ self nextPutAll: String cr
- !
- crlf
- ^ self nextPutAll: String crlf
- !
- lf
- ^ self nextPutAll: String lf
- !
- nextPut: aString
- self nextPutAll: aString
- !
- nextPutAll: aString
- | pre post |
- self atEnd ifTrue: [ self setCollection: self collection, aString ] ifFalse: [
- pre := self collection copyFrom: 1 to: self position.
- post := self collection copyFrom: (self position + 1 + aString size) to: self collection size.
- self setCollection: pre, aString, post
- ].
- self position: self position + aString size.
- self setStreamSize: (self streamSize max: self position)
- !
- nextPutString: aString
- self nextPutAll: aString
- !
- space
- self nextPut: ' '
- !
- tab
- ^ self nextPutAll: String tab
- ! !
|