[squeak-dev] The Trunk: Collections-ul.640.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Aug 14 20:25:55 UTC 2015


Levente Uzonyi uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-ul.640.mcz

==================== Summary ====================

Name: Collections-ul.640
Author: ul
Time: 12 August 2015, 10:35:29.572 pm
UUID: 1065564d-36c5-43a1-842b-3be19ce91a3e
Ancestors: Collections-cmm.639

Character:
- sped up various methods by storing and reusing the result of #asInteger in a temporary variable.
- sped up #isSeparator by eliminating the last branch. Swapped the tab and cr checks, because source code has more tabs than crs.
- unified methods with mixed #asInteger and #asciiValue sends
- #isAscii uses #< instead of #between:and:, like #isOctetCharacter does.
- #asUnicode uses the same shortcut as #encodedCharSet does
- quick return in #printOn: and #storeOn:

String:
- added identity check (should help with Text comparison) and quick returns to #=
- spaceship operator uses #compare: if the argument is a string
- added a fast #asSignedInteger implementation

Text:
- removed the identity check from Text >> #=, because String >> #= does it
- the spaceship operator uses String's spaceship operator

=============== Diff against Collections-cmm.639 ===============

Item was changed:
  ----- Method: Character>>< (in category 'comparing') -----
  < aCharacter 
  	"Answer true if the receiver's value < aCharacter's value."
  
+ 	^self asInteger < aCharacter asInteger!
- 	^self asInteger < aCharacter asciiValue!

Item was changed:
  ----- Method: Character>><= (in category 'comparing') -----
  <= aCharacter 
  	"Answer true if the receiver's value <= aCharacter's value."
  
+ 	^self asInteger <= aCharacter asInteger!
- 	^self asInteger <= aCharacter asciiValue!

Item was changed:
  ----- Method: Character>>> (in category 'comparing') -----
  > aCharacter 
  	"Answer true if the receiver's value > aCharacter's value."
  
+ 	^self asInteger > aCharacter asInteger!
- 	^self asInteger > aCharacter asciiValue!

Item was changed:
  ----- Method: Character>>>= (in category 'comparing') -----
  >= aCharacter 
  	"Answer true if the receiver's value >= aCharacter's value."
  
+ 	^self asInteger >= aCharacter asInteger!
- 	^self asInteger >= aCharacter asciiValue!

Item was changed:
  ----- Method: Character>>asLowercase (in category 'converting') -----
  asLowercase
  	"Answer the receiver's matching lowercase Character."
  	
+ 	| integerValue |
+ 	(integerValue := self asInteger) > 255 ifFalse: [ 
- 	self asInteger > 255 ifFalse: [ 
  		| result |
+ 		(result := (ClassificationTable at: integerValue + 1) bitAnd: 16rFF) > 0
- 		(result := (ClassificationTable at: self asInteger + 1) bitAnd: 16rFF) > 0
  			ifTrue: [ ^self class value: result ] ].
+ 	^self class value: (self encodedCharSet toLowercaseCode: integerValue)!
- 	^self class value: (self encodedCharSet toLowercaseCode: self asInteger)!

Item was changed:
  ----- Method: Character>>asUnicode (in category 'converting') -----
  asUnicode
  	"Answer the unicode encoding of the receiver"
+ 	
+ 	| integerValue |
+ 	(integerValue := self asInteger) <= 16r3FFFFF ifTrue: [ ^integerValue ].
+ 	^self encodedCharSet charsetClass convertToUnicode: (integerValue bitAnd: 16r3FFFFF)
- 	self leadingChar = 0 ifTrue: [^ self asInteger].
- 	^self encodedCharSet charsetClass convertToUnicode: self charCode
  !

Item was changed:
  ----- Method: Character>>asUppercase (in category 'converting') -----
  asUppercase
  	"Answer the receiver's matching uppercase Character."
  	
+ 	| integerValue |
+ 	(integerValue := self asInteger) > 255 ifFalse: [ 
- 	self asInteger > 255 ifFalse: [ 
  		| result |
+ 		(result := ((ClassificationTable at: integerValue + 1) bitShift: -8) bitAnd: 16rFF) > 0
- 		(result := ((ClassificationTable at: self asInteger + 1) bitShift: -8) bitAnd: 16rFF) > 0
  			ifTrue: [ ^self class value: result ] ].
+ 	^self class value: (self encodedCharSet toUppercaseCode: integerValue)!
- 	^self class value: (self encodedCharSet toUppercaseCode: self asInteger)!

Item was changed:
  ----- Method: Character>>digitValue (in category 'accessing') -----
  digitValue
  	"Answer 0-9 if the receiver is $0-$9, 10-35 if it is $A-$Z, and < 0 
  	otherwise. This is used to parse literal numbers of radix 2-36."
  
+ 	| integerValue |
+ 	(integerValue := self asInteger) > 16rFF ifTrue: [^self encodedCharSet digitValueOf: self].
+ 	^DigitValues at: integerValue + 1!
- 	self asInteger > 16rFF ifTrue: [^self encodedCharSet digitValueOf: self].
- 	^DigitValues at: 1 + self asInteger!

Item was changed:
  ----- Method: Character>>isAlphaNumeric (in category 'testing') -----
  isAlphaNumeric
  	"Answer whether the receiver is a letter or a digit."
  
+ 	| integerValue |
+ 	(integerValue := self asInteger) > 255 ifFalse: [ 
+ 		^((ClassificationTable at: integerValue + 1) bitAnd: AlphaNumericMask) > 0 ].
- 	self asInteger > 255 ifFalse: [ ^((ClassificationTable at: self asInteger + 1) bitAnd: AlphaNumericMask) > 0 ].
  	^self encodedCharSet isAlphaNumeric: self!

Item was changed:
  ----- Method: Character>>isAscii (in category 'testing') -----
  isAscii
+ 
+ 	^self asInteger < 128!
- 	^ self asInteger between: 0 and: 127!

Item was changed:
  ----- Method: Character>>isDigit (in category 'testing') -----
  isDigit
  
+ 	| integerValue |
+ 	(integerValue := self asInteger) > 255 ifFalse: [
+ 		^((ClassificationTable at: integerValue + 1) bitAnd: DigitBit) > 0 ].
- 	self asInteger > 255 ifFalse: [ ^((ClassificationTable at: self asInteger + 1) bitAnd: DigitBit) > 0 ].
  	^self encodedCharSet isDigit: self.
  !

Item was changed:
  ----- Method: Character>>isLetter (in category 'testing') -----
  isLetter
  
+ 	| integerValue |
+ 	(integerValue := self asInteger) > 255 ifFalse: [
+ 		^((ClassificationTable at: integerValue + 1) bitAnd: LetterMask) > 0 ].
- 	self asInteger > 255 ifFalse: [ ^((ClassificationTable at: self asInteger + 1) bitAnd: LetterMask) > 0 ].
  	^self encodedCharSet isLetter: self!

Item was changed:
  ----- Method: Character>>isLowercase (in category 'testing') -----
  isLowercase
  
+ 	| integerValue |
+ 	(integerValue := self asInteger) > 255 ifFalse: [
+ 		^((ClassificationTable at: integerValue + 1) bitAnd: LowercaseBit) > 0 ].
- 	self asInteger > 255 ifFalse: [ ^((ClassificationTable at: self asInteger + 1) bitAnd: LowercaseBit) > 0 ].
  	^self encodedCharSet isLowercase: self.
  !

Item was changed:
  ----- Method: Character>>isSeparator (in category 'testing') -----
  isSeparator
  	"Answer whether the receiver is one of the separator characters--space, 
  	cr, tab, line feed, or form feed."
  
+ 	| integerValue |
+ 	(integerValue := self asInteger) = 32 ifTrue: [ ^true ].	"space"
+ 	integerValue = 9 ifTrue: [ ^true ].	"tab"
+ 	integerValue = 13 ifTrue: [ ^true ].	"cr"
+ 	integerValue = 10 ifTrue: [ ^true ].	"line feed"
+ 	^integerValue = 12	"form feed"!
- 	self asInteger = 32 ifTrue: [^true].	"space"
- 	self asInteger = 13 ifTrue: [^true].	"cr"
- 	self asInteger = 9 ifTrue: [^true].	"tab"
- 	self asInteger = 10 ifTrue: [^true].	"line feed"
- 	self asInteger = 12 ifTrue: [^true].	"form feed"
- 	^false!

Item was changed:
  ----- Method: Character>>isUppercase (in category 'testing') -----
  isUppercase
  
+ 	| integerValue |
+ 	(integerValue := self asInteger) > 255 ifFalse: [
+ 		^((ClassificationTable at: integerValue + 1) bitAnd: UppercaseBit) > 0 ].
- 	self asInteger > 255 ifFalse: [ ^((ClassificationTable at: self asInteger + 1) bitAnd: UppercaseBit) > 0 ].
  	^self encodedCharSet isUppercase: self.
  !

Item was changed:
  ----- Method: Character>>printOn: (in category 'printing') -----
  printOn: aStream
+ 
+ 	| integerValue |
+ 	((integerValue := self asInteger) > 32 and: [ integerValue ~= 127 ]) ifTrue: [
+ 		aStream nextPut: $$; nextPut: self.
+ 		^self ].
+ 	(self class constantNameFor: self)
+ 		ifNotNil: [ :name | aStream nextPutAll: self class name; space; nextPutAll: name ]
+ 		ifNil: [ aStream nextPutAll: self class name; nextPutAll: ' value: '; print: integerValue ]!
- 	| name |
- 	(self asInteger > 32 and: [self asInteger ~= 127])
- 		ifTrue: [ aStream nextPut: $$; nextPut: self ]
- 		ifFalse: [
- 			name := self class constantNameFor: self.
- 			name notNil
- 				ifTrue: [ aStream nextPutAll: self class name; space; nextPutAll: name ]
- 				ifFalse: [ aStream nextPutAll: self class name; nextPutAll: ' value: '; print: self asInteger ] ].!

Item was changed:
  ----- Method: Character>>shouldBePrintedAsLiteral (in category 'testing') -----
  shouldBePrintedAsLiteral
  
+ 	| integerValue |
+ 	^((integerValue := self asInteger) between: 33 and: 255) and: [self asInteger ~= 127]!
- 	^(self asInteger between: 33 and: 255) and: [self asInteger ~= 127]!

Item was changed:
  ----- Method: Character>>storeBinaryOn: (in category 'printing') -----
  storeBinaryOn: aStream
  	"Store the receiver on a binary (file) stream"
  	
+ 	| integerValue |
+ 	(integerValue := self asInteger) < 256 
- 	self asInteger < 256 
  		ifTrue: [ aStream basicNextPut: self ]
+ 		ifFalse: [ aStream nextInt32Put: integerValue ]!
- 		ifFalse: [ aStream nextInt32Put: self asInteger ]!

Item was changed:
  ----- Method: Character>>storeDataOn: (in category 'object fileIn') -----
  storeDataOn: aDataStream
  	" Store characters in reference-like way, with value like instvar.
  	This is compatible with various Squeak Memory Systems"
  
  	aDataStream
  		beginInstance: self class
+ 			size: 1;
+ 		nextPut: self asInteger!
- 		size: 1.
- 	aDataStream nextPut: self asInteger.!

Item was changed:
  ----- Method: Character>>storeOn: (in category 'printing') -----
  storeOn: aStream
  	"Common character literals are preceded by '$', however special need to be encoded differently: for some this might be done by using one of the shortcut constructor methods for the rest we have to create them by ascii-value."
  
+ 	self shouldBePrintedAsLiteral ifTrue: [ 
+ 		aStream nextPut: $$; nextPut: self.
+ 		^self ].
+ 	(self class constantNameFor: self) ifNotNil: [ :name |
+ 		aStream nextPutAll: self class name; space; nextPutAll: name.
+ 		^self ].
+ 	aStream 
+ 		nextPut: $(; nextPutAll: self class name; 
+ 		nextPutAll: ' value: '; print: self asInteger; nextPut: $)!
- 	| name |
- 	self shouldBePrintedAsLiteral
- 		ifTrue: [ aStream nextPut: $$; nextPut: self ]
- 		ifFalse: [
- 			name := self class constantNameFor: self.
- 			name notNil
- 				ifTrue: [ aStream nextPutAll: self class name; space; nextPutAll: name ]
- 				ifFalse: [
- 					aStream 
- 						nextPut: $(; nextPutAll: self class name; 
- 						nextPutAll: ' value: '; print: self asInteger; nextPut: $) ] ].!

Item was changed:
  ----- Method: CharacterSet>>includes: (in category 'collection ops') -----
  includes: aCharacter
+ 
+ 	| index |
+ 	(index := aCharacter asInteger + 1) > 256 ifTrue: [ ^false ].
+ 	^(map at: index) > 0!
- 	aCharacter asciiValue >= 256
- 		ifTrue: ["Guard against wide characters"
- 			^false].
- 	^(map at: aCharacter asciiValue + 1) > 0!

Item was changed:
  ----- Method: String>><=> (in category 'sorting') -----
  <=> aCharacterArray
  	"Return a collation order of -1, 0, or 1, indicating whether I should be collated before the receiver, am equal, or after.
  	See also:  http://en.wikipedia.org/wiki/Spaceship_operator"
  
+ 	aCharacterArray isString ifTrue: [ ^(self compare: aCharacterArray) - 2 ].
+ 	self = aCharacterArray 	ifTrue: [ ^0 ].
+ 	self < aCharacterArray 	ifTrue: [ ^-1 ].
+ 	^1!
- 	^self = aCharacterArray
- 		ifTrue: [ 0 ]
- 		ifFalse: [self < aCharacterArray
- 			ifTrue: [ -1 ]
- 			ifFalse: [ 1 ]]!

Item was changed:
  ----- Method: String>>= (in category 'comparing') -----
  = aString 
  	"Answer whether the receiver sorts equally as aString.
  	The collation order is simple ascii (with case differences)."
  	
+ 	self == aString ifTrue: [ ^true ].
+ 	aString isString ifFalse: [ ^false ].
+ 	self size = aString size ifFalse: [ ^false ].
- 	(aString isString
- 	 and: [self size = aString size]) ifFalse: [^ false].
  	^ (self compare: self with: aString collated: AsciiOrder) = 2!

Item was changed:
  ----- Method: String>>asSignedInteger (in category 'converting') -----
  asSignedInteger
  	"Returns the first signed integer it can find or nil."
  
+ 	| result character index negative |
+ 	(self at: 1) isDigit
+ 		ifTrue: [ index := 1 ]
+ 		ifFalse: [ 
+ 			index := self findFirst: [ :char | char isDigit ].
+ 			index = 0 ifTrue: [ ^nil ] ].
+ 	negative := index > 1 and: [ (self at: index - 1) == $- ].
+ 	result := 0.
+ 	[ index <= self size and: [ (character := self at: index) isDigit ] ] whileTrue: [
+ 		result := result * 10 + character asciiValue - 48 "$0 asciiValue".
+ 		index := index + 1 ].
+ 	negative ifTrue: [ ^0 - result ].
+ 	^result
+ !
- 	| start |
- 	start := self findFirst: [:char | char isDigit].
- 	start isZero ifTrue: [^ nil].
- 	(start > 1 and: [self at: start - 1]) = $- ifTrue: [start := start - 1].
- 	^ Integer readFrom: (ReadStream on: self from: start to: self size)!

Item was changed:
  ----- Method: Text>><=> (in category 'sorting') -----
  <=> aCharacterArray
  	"Return a collation order of -1, 0, or 1, indicating whether I should be collated before the receiver, am equal, or after.
  	See also:  http://en.wikipedia.org/wiki/Spaceship_operator"
  
+ 	aCharacterArray isString ifTrue: [ ^string <=> aCharacterArray ].
+ 	^string <=> aCharacterArray asString!
- 	^string = aCharacterArray
- 		ifTrue: [ 0 ]
- 		ifFalse: [string < aCharacterArray asString
- 			ifTrue: [ -1 ]
- 			ifFalse: [ 1 ]]!

Item was changed:
  ----- Method: Text>>= (in category 'comparing') -----
  = other
  	"Am I equal to the other Text or String?  
  	***** Warning ***** Two Texts are considered equal if they have the same characters in them.  They might have completely different emphasis, fonts, sizes, text actions, or embedded morphs.  If you need to find out if one is a true copy of the other, you must do (text1 = text2 and: [text1 runs = text2 runs])."
  
+ 	other isText ifTrue:	[ ^string = other string ].
+ 	other isString ifTrue: [ ^string = other ].
+ 	^false!
- 	other isText ifTrue:	["This is designed to run fast even for megabytes"
- 				^ string == other string or: [string = other string]].
- 	other isString ifTrue: [^ string == other or: [string = other]].
- 	^ false!



More information about the Squeak-dev mailing list