Smalltalk createPackage: 'Kernel-Collections'! Object subclass: #Association slots: {#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 slots: {#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 ! hashBlock: aBlock hashBlock := aBlock ! ! !BucketStore methodsFor: 'adding/removing'! removeAll ! ! !BucketStore methodsFor: 'enumerating'! 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 slots: {} package: 'Kernel-Collections'! !ArrayBucketStore commentStamp! I am a concrete `BucketStore` with buckets being instance of `Array`.! !ArrayBucketStore methodsFor: 'private'! newBucket ^ #() ! ! Object subclass: #Collection slots: {} 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'! 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 ] ! 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 ! single "Answer a single element. Raise an error if collection holds less or more than one element." self ifEmpty: [ self error: 'Collection is empty' ]. self size > 1 ifTrue: [ self error: 'Collection holds more than one element' ]. ^ self anyOne ! size self subclassResponsibility ! ! !Collection methodsFor: 'adding/removing'! add: anObject self subclassResponsibility ! addAll: aCollection aCollection do: [ :each | self add: each ]. ^ aCollection ! remove: anObject ^ self remove: anObject ifAbsent: [ self errorNotFound ] ! remove: anObject ifAbsent: aBlock self subclassResponsibility ! removeAll self subclassResponsibility ! ! !Collection methodsFor: 'converting'! asArray ^ Array withAll: self ! asJavaScriptObject ^ self asArray collect: [ :each | each asJavaScriptObject ] ! asOrderedCollection ^ self asArray ! asSet ^ Set withAll: self ! ! !Collection methodsFor: 'copying'! , aCollection ^ self copy addAll: aCollection; yourself ! copyEmpty ^ self class new ! copyWith: anObject ^ self copy add: anObject; yourself ! copyWithAll: aCollection self deprecatedAPI: 'Use #, instead.'. ^ self, aCollection ! copyWithout: anObject "Answer a copy of the receiver that does not contain any occurrences of anObject." ^ self reject: [ :each | each = anObject ] ! 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 ] ! deepCopy ^ self collect: [ :each | each deepCopy ] ! shallowCopy ^ self collect: [ :each | 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 do: [ :each | (aBlock value: each) ifTrue: [ ^each ] ]. ^ anotherBlock value ! 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: 'printing'! shortenedPrintString ^ self size <= 1 ifTrue: [ self printString ] ifFalse: [ (self copyEmpty copyWith: self anyOne) printString, ' ... ', (self size - 1) asString, ' more items' ] ! ! !Collection methodsFor: 'streaming'! putOn: aStream self do: [ :each | each putOn: aStream ] ! ! !Collection methodsFor: 'testing'! 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" [ aBlock value ] ifFalse: [ self ] ! ifEmpty: aBlock ifNotEmpty: anotherBlock ^ self isEmpty ifTrue: "aBlock" [ aBlock value ] 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" [ anotherBlock value ] ! includes: anObject ^ self anySatisfy: [ :each | each = anObject ] ! isEmpty ^ self size = 0 ! notEmpty ^ self isEmpty not ! ! !Collection class methodsFor: 'accessing'! classTag "Returns a tag or general category for this class. Typically used to help tools do some reflection. Helios, for example, uses this to decide what icon the class should display." ^ '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: #AssociativeCollection slots: {} 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'! = anAssociativeCollection ^ self class = anAssociativeCollection class and: [ self size = anAssociativeCollection size and: [ | comparisons | comparisons := OrderedCollection new. (self associations allSatisfy: [ :each | anAssociativeCollection at: each key ifPresent: [ :otherValue | comparisons add: { each value. otherValue }. true ] ifAbsent: [ false ] ]) and: [ comparisons allSatisfy: [ :each | each first = each second ] ] ] ] ! ! !AssociativeCollection methodsFor: 'converting'! asDictionary ^ Dictionary from: self associations ! asHashedCollection ^ HashedCollection from: self associations ! asJavaScriptObject | hash | hash := HashedCollection new. self keysAndValuesDo: [ :key :value | hash at: key put: value asJavaScriptObject ]. ^ 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 ! select: selectBlock thenCollect: collectBlock | newDict | newDict := self class new. self keysAndValuesDo: [ :key :value | (selectBlock value: value) ifTrue: [ newDict at: key put: (collectBlock value: 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: ')' ! shortenedPrintString ^ self size <= 1 ifTrue: [ self printString ] ifFalse: [ | key | key := self keys anyOne. (self copyEmpty at: key put: (self at: key); yourself) printString, ' ... ', (self size - 1) asString, ' more items' ] ! ! !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 slots: {#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 =0 ? $self.values[index] : aBlock._value(); '> ! at: aKey put: 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 ! ! !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 ! ! !Dictionary methodsFor: 'testing'! includesKey: aKey = 0;'> ! ! AssociativeCollection subclass: #HashedCollection slots: {} 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'! asJavaScriptSource ^ self ifEmpty: [ '{}' ] ifNotEmpty: [ String streamContents: [ :str | str nextPut: '{'. self keysAndValuesDo: [ :key :value | str nextPutAll: key asJavaScriptSource; nextPut: ':'; nextPutAll: value asJavaScriptSource; nextPut: ',' ]. str skip: -1; nextPut: '}' ] ] ! at: aKey ifAbsent: aBlock ^ (self includesKey: aKey) ifTrue: [ self basicAt: aKey ] ifFalse: [ aBlock value ] ! at: aKey put: aValue ^ self basicAt: aKey put: aValue ! keys ! values ! ! !HashedCollection methodsFor: 'adding/removing'! removeKey: aKey ifAbsent: aBlock ^ self at: aKey ifPresent: [ :removed | self basicDelete: aKey. removed ] ifAbsent: [ aBlock value ] ! ! !HashedCollection methodsFor: 'converting'! jsonLiteralized ^ JSON parse: (JSON stringify: self) ! ! !HashedCollection methodsFor: 'enumerating'! keysDo: aBlock self keys do: aBlock ! valuesDo: aBlock self values do: aBlock ! ! !HashedCollection methodsFor: 'testing'! includesKey: aKey ! ! Collection subclass: #SequenceableCollection slots: {} 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 ! anyOne ^ self at: 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 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 subclassResponsibility ! 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 self subclassResponsibility ! copyWithFirst: anObject ^ (self class with: anObject) addAll: self; yourself ! ! !SequenceableCollection methodsFor: 'enumerating'! pairsCollect: aBlock "Evaluate aBlock with my elements taken two at a time, and return an Array with the results" "(#(1 'fred' 2 'charlie' 3 'elmer') pairsCollect: [:a :b | b, ' is number ', a printString]) >>> #('fred is number 1' 'charlie is number 2' 'elmer is number 3')" ^ (1 to: self size // 2) collect: [ :index | aBlock value: (self at: 2 * index - 1) value: (self at: 2 * index) ] ! pairsDo: aBlock "Evaluate aBlock with my elements taken two at a time. If there's an odd number of items, ignore the last one. Allows use of a flattened array for things that naturally group into pairs. See also pairsCollect:" "(#(1 'fred' 2 'charlie' 3 'elmer') pairsDo: [:a :b | Transcript cr; show: b, ' is number ', a printString]) >>> #(1 'fred' 2 'charlie' 3 'elmer')" 1 to: self size // 2 do: [ :index | aBlock value: (self at: 2 * index - 1) value: (self at: 2 * index) ] ! reverseDo: aBlock self reversed do: aBlock ! ! !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 slots: {} 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 put: anObject ! ! !Array methodsFor: 'adding/removing'! add: anObject ! addAll: aCollection ! addFirst: anObject ! remove: anObject ifAbsent: aBlock | index | index := self indexOf: anObject ifAbsent: [ 0 ]. ^ index = 0 ifFalse: [ self removeIndex: index. anObject ] ifTrue: [ aBlock value ] ! removeAll ! removeFrom: aNumber to: anotherNumber ! removeIndex: anInteger ! removeLast ! ! !Array methodsFor: 'converting'! asJavaScriptSource ^ '[', ((self collect: [:each | each asJavaScriptSource ]) join: ', '), ']' ! reversed ! ! !Array methodsFor: 'copying'! appendToString: aString ! copyFrom: anIndex to: anotherIndex = 1 && anotherIndex <= self.length) { return self.slice(anIndex - 1, anotherIndex); } else { self._at_(anIndex); self._at_(self.length + 1); throw new Error("Incorrect indexes in #copyFrom:to: not caught by #at:"); } '> ! shallowCopy ! ! !Array methodsFor: 'enumerating'! allIn: aBlock ^ aBlock valueWithPossibleArguments: "collect to match #in: behaviour" (self collect: [ :each | each in: [ :x | x ] ]) ! collect: aBlock "Optimized version" ! join: aString ! select: aBlock "Optimized version" ! sort ^ self sort: [ :a :b | a < b ] ! sort: aBlock ! 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 class methodsFor: 'instance creation'! new: 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: #String slots: {} 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 ! at: anIndex ifAbsent: aBlock ! at: anIndex ifPresent: aBlock ifAbsent: anotherBlock ! at: anIndex put: anObject self errorReadOnly ! charCodeAt: anInteger ! ! !String methodsFor: 'adding/removing'! add: anObject self errorReadOnly ! remove: anObject self errorReadOnly ! remove: anObject ifAbsent: aBlock self errorReadOnly ! ! !String methodsFor: 'comparing'! < aString ! <= aString ! = aString ! == aString ! > aString aString : $recv(aString)._isStringGreaterThanSelf_(String(self))'> ! >= aString = aString : $recv(aString)._isStringGreaterThanOrEqualSelf_(String(self))'> ! isStringEqualToSelf: aString ! isStringGreaterThanOrEqualToSelf: aString = self'> ! isStringGreaterThanSelf: aString self'> ! isStringLessThanOrEqualToSelf: aString ! isStringLessThanSelf: aString ! ! !String methodsFor: 'converting'! asJavaScriptMethodName ! asJavaScriptObject ^ self ! asJavaScriptSource ! asLowercase ! asMutator "Answer a setter selector. For example, #name asMutator returns #name:" self last = ':' ifFalse: [ ^ self, ':' ]. ^ self ! asNumber ! asRegexp ^ RegularExpression fromString: self ! asString ^ self ! asSymbol ^ self ! asUppercase ! capitalized ^ self ifNotEmpty: [ self first asUppercase, self allButFirst ] ! crlfSanitized ^ self lines join: String lf ! escaped ! reversed ! unescaped ! uriComponentDecoded ! uriComponentEncoded ! uriDecoded ! uriEncoded ! ! !String methodsFor: 'copying'! , aString ! appendToString: aString ! copyFrom: anIndex to: anotherIndex ! copyWithFirst: anObject (anObject isString and: [ anObject size = 1 ]) "character is one-char string in JS" ifFalse: [ self error: 'Cannot put ', anObject class name, ' in a String' ]. ^ anObject, self ! deepCopy ^ self shallowCopy ! shallowCopy ^ self ! ! !String methodsFor: 'error handling'! errorReadOnly self error: 'Object is read-only' ! ! !String methodsFor: 'evaluating'! value: anObject ^ anObject perform: self ! ! !String methodsFor: 'printing'! asSymbolPrintOn: aStream aStream nextPutAll: '#'. self asString isSelector ifTrue: [ aStream nextPut: self ] ifFalse: [ self printOn: aStream ] ! printNl ! printOn: aStream aStream nextPutAll: ''''; nextPutAll: (self replace: '''' with: ''''''); nextPutAll: '''' ! shortenedPrintString ^ self printString size > 30 ifTrue: [ (self printString copyFrom: 1 to: 30), '...''' ] ifFalse: [ self printString ] ! symbolPrintString ^ String streamContents: [ :str | self asSymbolPrintOn: str ] ! ! !String methodsFor: 'regular expressions'! match: aRegexp ! matchesOf: aRegularExpression ! replace: aString with: anotherString ^ self replaceRegexp: (RegularExpression fromString: aString flag: 'g') with: anotherString ! replaceRegexp: aRegexp with: 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." ! 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 lines do: aBlock ! subStrings: aString ^ self tokenize: aString ! tokenize: aString ! ! !String methodsFor: 'streaming'! putOn: aStream aStream nextPutString: self ! ! !String methodsFor: 'testing'! includesSubString: subString ! isCapitalized ^ self first asUppercase == self first ! isImmutable ^ true ! isSelector <,@%~|&-]+|([a-zA-Z][a-zA-Z0-9]*\:)+)$/)' > ! 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 ! crlf ! esc ^ self fromCharCode: 27 ! lf ! space ! streamClass ^ StringStream ! tab ! ! !String class methodsFor: 'instance creation'! fromCharCode: anInteger ! fromString: aString ! value: aUTFCharCode ! ! !String class methodsFor: 'random'! random "Returns random alphanumeric string beginning with letter" ! randomNotIn: aString | result | [ result := self random. aString includesSubString: result ] whileTrue. ^ result ! ! Collection subclass: #Set slots: {#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: [ | obj | obj := bucket first. bucket third remove: obj ifAbsent: [ ^aBlock value ]. size := size - 1. obj ] ifNotNil: [ :primitiveBucket | self remove: bucket first in: primitiveBucket ifAbsent: aBlock ] ! removeAll ! ! !Set methodsFor: 'comparing'! = aCollection ^ self class = aCollection class and: [ self size = aCollection size and: [ self allSatisfy: [ :each | aCollection includes: each ] ] ] ! ! !Set methodsFor: 'enumerating'! collect: aBlock | collection | collection := self class new. self do: [ :each | collection add: (aBlock value: each) ]. ^ collection ! do: aBlock ! select: aBlock | collection | collection := self class new. self do: [ :each | (aBlock value: each) ifTrue: [ collection add: each ] ]. ^ collection ! select: selectBlock thenCollect: collectBlock | collection | collection := self class new. self do: [ :each | (selectBlock value: each) ifTrue: [ collection add: (collectBlock value: 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 ! 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" ! classNameOf: anObject "Answer the class name of `anObject`, or `undefined` if `anObject` is not an Smalltalk object" ! includes: anObject in: anotherObject ! jsConstructorNameOf: anObject ! remove: anObject in: anotherObject ifAbsent: aBlock ! ! !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: #ProtoStream slots: {} package: 'Kernel-Collections'! !ProtoStream commentStamp! I am the abstract base for different accessor for a sequence of objects. This sequence is referred to as my "contents". My instances are read/write streams modifying the contents.! !ProtoStream methodsFor: 'accessing'! contents self subclassResponsibility ! ! !ProtoStream methodsFor: 'actions'! reset self subclassResponsibility ! resetContents self subclassResponsibility ! ! !ProtoStream methodsFor: 'enumerating'! do: aBlock [ self atEnd ] whileFalse: [ aBlock value: self next ] ! ! !ProtoStream methodsFor: 'positioning'! setToEnd self subclassResponsibility ! setToStart self reset ! ! !ProtoStream methodsFor: 'reading'! next ^ self atEnd ifTrue: [ nil ] ifFalse: [ self subclassResponsibility ] ! peek ^ self atEnd ifTrue: [ nil ] ifFalse: [ self subclassResponsibility ] ! ! !ProtoStream methodsFor: 'testing'! atEnd self subclassResponsibility ! atStart self subclassResponsibility ! isEmpty ^ self atStart and: [ self atEnd ] ! ! !ProtoStream methodsFor: 'writing'! << anObject self write: anObject ! nextPut: anObject self subclassResponsibility ! nextPutAll: aCollection aCollection do: [ :each | self nextPut: each ] ! nextPutString: aString self nextPut: aString ! write: anObject anObject putOn: self ! ! !ProtoStream class methodsFor: 'instance creation'! on: aCollection ^ self new setCollection: aCollection; setStreamSize: aCollection size; yourself ! ! ProtoStream subclass: #Stream slots: {#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: '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'! nextPut: anObject self position: self position + 1. self collection at: self position put: anObject. self setStreamSize: (self streamSize max: self position) ! ! !Stream class methodsFor: 'instance creation'! on: aCollection ^ self new setCollection: aCollection; setStreamSize: aCollection size; yourself ! ! Stream subclass: #StringStream slots: {} 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 position = self collection size 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 ! print: anObject anObject printOn: self ! printSymbol: anObject anObject asSymbolPrintOn: self ! space self nextPut: ' ' ! tab ^ self nextPutAll: String tab ! ! Object subclass: #Queue slots: {#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 ifEmpty: [ 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 slots: {} package: 'Kernel-Collections'! !RegularExpression commentStamp! I represent a regular expression object. My instances are JavaScript `RegExp` object.! !RegularExpression methodsFor: 'evaluating'! compile: aString ! exec: aString ! test: aString ! ! !RegularExpression class methodsFor: 'instance creation'! fromString: aString ^ self fromString: aString flag: '' ! fromString: aString flag: anotherString ! ! Trait named: #TKeyValueCollection package: 'Kernel-Collections'! !TKeyValueCollection 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 ! ! !TKeyValueCollection 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 ! ! Trait named: #TNativeZeroBasedCollection package: 'Kernel-Collections'! !TNativeZeroBasedCollection methodsFor: 'accessing'! at: anIndex ifAbsent: aBlock = 1 && anIndex <= self.length ? self[anIndex - 1] : aBlock._value() '> ! at: anIndex ifPresent: aBlock ifAbsent: anotherBlock = 1 && anIndex <= self.length ? aBlock._value_(self[anIndex - 1]) : anotherBlock._value() '> ! indexOf: anObject ifAbsent: aBlock ! indexOf: anObject startingAt: start ifAbsent: aBlock ! single 1) throw new Error("Collection holds more than one element."); return self[0]; '> ! size ! ! !TNativeZeroBasedCollection methodsFor: 'enumerating'! detect: aBlock ifNone: anotherBlock ! do: aBlock ! with: anotherCollection do: aBlock ! withIndexDo: aBlock ! ! AssociativeCollection setTraitComposition: {TKeyValueCollection} asTraitComposition! SequenceableCollection setTraitComposition: {TKeyValueCollection} asTraitComposition! Array setTraitComposition: {TNativeZeroBasedCollection} asTraitComposition! String setTraitComposition: {TNativeZeroBasedCollection} asTraitComposition! ! !