<div dir="ltr"><div>Sorry for introducing a few Undeclared at this stage...<br></div>They should disappear at next update.<br></div><div class="gmail_extra"><br><div class="gmail_quote">2017-12-01 1:25 GMT+01:00  <span dir="ltr"><<a href="mailto:commits@source.squeak.org" target="_blank">commits@source.squeak.org</a>></span>:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Nicolas Cellier uploaded a new version of Collections to project The Trunk:<br>
<a href="http://source.squeak.org/trunk/Collections-nice.775.mcz" rel="noreferrer" target="_blank">http://source.squeak.org/<wbr>trunk/Collections-nice.775.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: Collections-nice.775<br>
Author: nice<br>
Time: 1 December 2017, 1:25:19.882602 am<br>
UUID: 5ef7a80c-6213-4e8e-8f0c-<wbr>b45e110ce15e<br>
Ancestors: Collections-nice.774<br>
<br>
Rename CharacterSet -> ByteCharacterSet<br>
<br>
This is step 1:<br>
- create a parallel ByteCharacterSet<br>
- then mutate CharacterSet instances -> ByteCharacterSet in postscript<br>
<br>
=============== Diff against Collections-nice.774 ===============<br>
<br>
Item was added:<br>
+ ----- Method: AbstractCharacterSet>>species (in category 'private') -----<br>
+ species<br>
+       ^CharacterSet!<br>
<br>
Item was added:<br>
+ Collection subclass: #ByteCharacterSet<br>
+       instanceVariableNames: 'byteArrayMap tally'<br>
+       classVariableNames: 'CrLf NonSeparators Separators'<br>
+       poolDictionaries: ''<br>
+       category: 'Collections-Support'!<br>
+<br>
+ !ByteCharacterSet commentStamp: '<historical>' prior: 0!<br>
+ A set of characters.  Lookups for inclusion are very fast.!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet class>>allCharacters (in category 'instance creation') -----<br>
+ allCharacters<br>
+       "return a set containing all characters"<br>
+<br>
+       | set |<br>
+       set := self empty.<br>
+       0 to: 255 do: [ :ascii | set add: (Character value: ascii) ].<br>
+       ^set!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet class>>cleanUp: (in category 'initialize-release') -----<br>
+ cleanUp: aggressive<br>
+<br>
+       CrLf := NonSeparators := Separators := nil!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet class>>crlf (in category 'accessing') -----<br>
+ crlf<br>
+<br>
+       ^CrLf ifNil: [ CrLf := self with: Character cr with: Character lf ]!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet class>>empty (in category 'instance creation') -----<br>
+ empty<br>
+       "return an empty set of characters"<br>
+       ^self new!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet class>>newFrom: (in category 'instance creation') -----<br>
+ newFrom: aCollection<br>
+       | newCollection |<br>
+       newCollection := self new.<br>
+       newCollection addAll: aCollection.<br>
+       ^newCollection!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet class>>nonSeparators (in category 'accessing') -----<br>
+ nonSeparators<br>
+       "return a set containing everything but the whitespace characters"<br>
+<br>
+       ^NonSeparators ifNil: [<br>
+               NonSeparators := self separators complement ]!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet class>>separators (in category 'accessing') -----<br>
+ separators<br>
+       "return a set containing just the whitespace characters"<br>
+<br>
+       ^Separators ifNil: [ Separators := self newFrom: Character separators ]!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet class>>withAll: (in category 'instance creation') -----<br>
+ withAll: aCollection<br>
+       "Create a new ByteCharacterSet containing all the characters from aCollection."<br>
+<br>
+       ^self newFrom: aCollection!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>= (in category 'comparing') -----<br>
+ = anObject<br>
+<br>
+       self species == anObject species ifFalse: [ ^false ].<br>
+       anObject size = tally ifFalse: [ ^false ].<br>
+       ^self byteArrayMap = anObject byteArrayMap!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>add: (in category 'adding') -----<br>
+ add: aCharacter<br>
+       "I automatically become a WideByteCharacterSet if you add a wide character to myself"<br>
+<br>
+       | index |<br>
+       (index := aCharacter asInteger + 1) <= 256 ifFalse: [<br>
+               | wide |<br>
+               wide := WideCharacterSet new.<br>
+               wide addAll: self.<br>
+               wide add: aCharacter.<br>
+               self becomeForward: wide.<br>
+               ^aCharacter ].<br>
+       (byteArrayMap at: index) = 1 ifFalse: [<br>
+               byteArrayMap at: index put: 1.<br>
+               tally := tally + 1 ].<br>
+       ^aCharacter!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>asString (in category 'conversion') -----<br>
+ asString<br>
+       "Convert the receiver into a String"<br>
+<br>
+       ^String new: self size streamContents:[:s|<br>
+               self do:[:ch| s nextPut: ch].<br>
+       ].!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>byteArrayMap (in category 'private') -----<br>
+ byteArrayMap<br>
+       "return a ByteArray mapping each ascii value to a 1 if that ascii value is in the set, and a 0 if it isn't.  Intended for use by primitives only"<br>
+       ^byteArrayMap!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>><wbr>byteComplement (in category 'conversion') -----<br>
+ byteComplement<br>
+       "return a character set containing precisely the single byte characters the receiver does not"<br>
+<br>
+       | set |<br>
+       set := ByteCharacterSet allCharacters.<br>
+       self do: [ :c | set remove: c ].<br>
+       ^set!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>complement (in category 'conversion') -----<br>
+ complement<br>
+       "return a character set containing precisely the characters the receiver does not"<br>
+<br>
+       ^ByteCharacterSetComplement of: self copy!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>do: (in category 'enumerating') -----<br>
+ do: aBlock<br>
+       "evaluate aBlock with each character in the set"<br>
+<br>
+       | index |<br>
+       tally >= 128 ifTrue: [ "dense"<br>
+               index := 0.<br>
+               [ (index := index + 1) <= 256 ] whileTrue: [<br>
+                       (byteArrayMap at: index) = 1 ifTrue: [<br>
+                               aBlock value: (Character value: index - 1) ] ].<br>
+               ^self ].<br>
+       "sparse"<br>
+       index := 0.<br>
+       [ (index := byteArrayMap indexOf: 1 startingAt: index + 1) = 0 ] whileFalse: [<br>
+               aBlock value: (Character value: index - 1) ].<br>
+       !<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>><wbr>findFirstInByteString:<wbr>startingAt: (in category 'zap me later') -----<br>
+ findFirstInByteString: aByteString startingAt: startIndex<br>
+       "Double dispatching: since we know this is a ByteString, we can use a superfast primitive using a ByteArray map with 0 slots for byte characters not included and 1 for byte characters included in the receiver."<br>
+       ^ByteString<br>
+               findFirstInString: aByteString<br>
+               inSet: self byteArrayMap<br>
+               startingAt: startIndex!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>><wbr>hasWideCharacters (in category 'testing') -----<br>
+ hasWideCharacters<br>
+       ^false!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>hash (in category 'comparing') -----<br>
+ hash<br>
+       ^self byteArrayMap hash!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>includes: (in category 'testing') -----<br>
+ includes: anObject<br>
+<br>
+       | index |<br>
+       anObject isCharacter ifFalse: [ ^false ].<br>
+       (index := anObject asInteger + 1) > 256 ifTrue: [ ^false ].<br>
+       ^(byteArrayMap at: index) > 0!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>initialize (in category 'private') -----<br>
+ initialize<br>
+<br>
+       byteArrayMap := ByteArray new: 256.<br>
+       tally := 0!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>isEmpty (in category 'testing') -----<br>
+ isEmpty<br>
+       ^tally = 0!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>><wbr>occurrencesOf: (in category 'zap me later') -----<br>
+ occurrencesOf: anObject<br>
+       "Answer how many of the receiver's elements are equal to anObject. Optimized version."<br>
+<br>
+       (self includes: anObject) ifTrue: [ ^1 ].<br>
+       ^0!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>postCopy (in category 'copying') -----<br>
+ postCopy<br>
+       super postCopy.<br>
+       byteArrayMap := byteArrayMap copy!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>remove: (in category 'removing') -----<br>
+ remove: aCharacter<br>
+<br>
+       ^self remove: aCharacter ifAbsent: aCharacter!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>remove:<wbr>ifAbsent: (in category 'removing') -----<br>
+ remove: aCharacter ifAbsent: aBlock<br>
+<br>
+       | index |<br>
+       (index := aCharacter asciiValue + 1) <= 256 ifFalse: [ ^aBlock value ].<br>
+       (byteArrayMap at: index) = 0 ifTrue: [ ^aBlock value ].<br>
+       byteArrayMap at: index put: 0.<br>
+       tally := tally - 1.<br>
+       ^aCharacter!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>removeAll (in category 'removing') -----<br>
+ removeAll<br>
+<br>
+       byteArrayMap atAllPut: 0.<br>
+       tally := 0!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>size (in category 'accessing') -----<br>
+ size<br>
+<br>
+       ^tally!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>species (in category 'zap me later') -----<br>
+ species<br>
+       ^CharacterSet!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>>union: (in category 'enumerating') -----<br>
+ union: aCollection<br>
+       (self species = aCollection species or: [aCollection isString or: [aCollection allSatisfy: [:e | e isCharacter]]]) ifFalse: [^super union: aCollection].<br>
+       (self species = aCollection species and: [self class ~= aCollection class]) ifTrue: [^aCollection union: self].<br>
+       ^self copy addAll: aCollection; yourself!<br>
<br>
Item was added:<br>
+ ----- Method: ByteCharacterSet>><wbr>wideCharacterMap (in category 'private') -----<br>
+ wideCharacterMap<br>
+       "used for comparing with WideByteCharacterSet"<br>
+<br>
+       | wide |<br>
+       wide := WideByteCharacterSet new.<br>
+       wide addAll: self.<br>
+       ^wide wideCharacterMap!<br>
<br>
Item was changed:<br>
  ----- Method: CharacterSet class>>crlf (in category 'accessing') -----<br>
  crlf<br>
<br>
+       ^CrLf ifNil: [ CrLf := ByteCharacterSet with: Character cr with: Character lf ]!<br>
-       ^CrLf ifNil: [ CrLf := self with: Character cr with: Character lf ]!<br>
<br>
Item was changed:<br>
  ----- Method: CharacterSet class>>empty (in category 'instance creation') -----<br>
  empty<br>
        "return an empty set of characters"<br>
+       ^ByteCharacterSet new!<br>
-       ^self new!<br>
<br>
Item was changed:<br>
  ----- Method: CharacterSet class>>newFrom: (in category 'instance creation') -----<br>
  newFrom: aCollection<br>
        | newCollection |<br>
+       newCollection := ByteCharacterSet new.<br>
-       newCollection := self new.<br>
        newCollection addAll: aCollection.<br>
        ^newCollection!<br>
<br>
Item was removed:<br>
- ----- Method: CharacterSetComplement>><wbr>findFirstInByteString:<wbr>startingAt: (in category 'enumerating') -----<br>
- findFirstInByteString: aByteString startingAt: startIndex<br>
-       "Double dispatching: since we know this is a ByteString, we can use a superfast primitive using a ByteArray map with 0 slots for byte characters not included and 1 for byte characters included in the receiver."<br>
-       ^ByteString<br>
-               findFirstInString: aByteString<br>
-               inSet: self byteArrayMap<br>
-               startingAt: startIndex!<br>
<br>
Item was removed:<br>
- ----- Method: WideCharacterSet>><wbr>findFirstInByteString:<wbr>startingAt: (in category 'enumerating') -----<br>
- findFirstInByteString: aByteString startingAt: startIndex<br>
-       "Double dispatching: since we know this is a ByteString, we can use a superfast primitive using a ByteArray map with 0 slots for byte characters not included and 1 for byte characters included in the receiver."<br>
-<br>
-       ^ByteString<br>
-               findFirstInString: aByteString<br>
-               inSet: byteArrayMap<br>
-               startingAt: startIndex!<br>
<br>
Item was removed:<br>
- ----- Method: WideCharacterSet>>species (in category 'comparing') -----<br>
- species<br>
-       ^self hasWideCharacters<br>
-               ifTrue: [WideCharacterSet]<br>
-               ifFalse: [CharacterSet]!<br>
<br>
Item was changed:<br>
+ (PackageInfo named: 'Collections') postscript: 'CharacterSet allInstancesDo: [:e | ByteCharacterSet adoptInstance: e ]'!<br>
- (PackageInfo named: 'Collections') postscript: 'CharacterSet allInstancesDo: #size'!<br>
<br>
<br>
</blockquote></div><br></div>