[Pkg] The Trunk: Collections-ul.406.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Nov 15 09:39:04 UTC 2010


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

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

Name: Collections-ul.406
Author: ul
Time: 15 November 2010, 10:30:39.825 am
UUID: 9cd8fc97-4673-3340-9ea2-2f3dbd5f38e3
Ancestors: Collections-cmm.405

- use #= for integer comparison instead of #== (http://bugs.squeak.org/view.php?id=2788 )

=============== Diff against Collections-cmm.405 ===============

Item was changed:
  ----- Method: SequenceableCollection>>after:ifAbsent: (in category 'accessing') -----
  after: target ifAbsent: exceptionBlock
  	"Answer the element after target.  Answer the result of evaluation
  	the exceptionBlock if target is not in the receiver, or if there are 
  	no elements after it."
  
  	| index |
  	index := self indexOf: target.
+ 	^ (index = 0 or: [index = self size])
- 	^ (index == 0 or: [index = self size])
  		ifTrue: [exceptionBlock value]
  		ifFalse: [self at: index + 1]!

Item was changed:
  ----- Method: SequenceableCollection>>before:ifAbsent: (in category 'accessing') -----
  before: target ifAbsent: exceptionBlock
  	"Answer the receiver's element immediately before target. Answer
  	the result of evaluating the exceptionBlock if target is not an element
  	of the receiver, or if there are no elements before it."
  
  	| index |
  	index := self indexOf: target.
+ 	^ (index = 0 or: [index = 1])
- 	^ (index == 0 or: [index == 1])
  		ifTrue: [exceptionBlock value]
  		ifFalse: [self at: index - 1]!

Item was changed:
  ----- Method: String>>asIdentifier: (in category 'converting') -----
  asIdentifier: shouldBeCapitalized
  	"Return a legal identifier, with first character in upper case if shouldBeCapitalized is true, else lower case.  This will always return a legal identifier, even for an empty string"
  
  	| aString firstChar firstLetterPosition |
  	aString := self select: [:el | el isAlphaNumeric].
  	firstLetterPosition := aString findFirst: [:ch | ch isLetter].
+ 	aString := firstLetterPosition = 0
- 	aString := firstLetterPosition == 0
  		ifFalse:
  			[aString copyFrom: firstLetterPosition to: aString size]
  		ifTrue:
  			['a', aString].
  	firstChar := shouldBeCapitalized ifTrue: [aString first asUppercase] ifFalse: [aString first asLowercase].
  
  	^ firstChar asString, (aString copyFrom: 2 to: aString size)
  "
  '234Fred987' asIdentifier: false
  '235Fred987' asIdentifier: true
  '' asIdentifier: true
  '()87234' asIdentifier: false
  '())z>=PPve889  U >' asIdentifier: false
  
  "!

Item was changed:
  ----- Method: String>>initialIntegerOrNil (in category 'converting') -----
  initialIntegerOrNil
  	"Answer the integer represented by the leading digits of the receiver, or nil if the receiver does not begin with a digit"
  	| firstNonDigit |
+ 	(self size = 0 or: [self first isDigit not]) ifTrue: [^ nil].
- 	(self size == 0 or: [self first isDigit not]) ifTrue: [^ nil].
  	firstNonDigit := (self findFirst: [:m | m isDigit not]).
  	firstNonDigit = 0 ifTrue: [firstNonDigit := self size + 1].
  	^ (self copyFrom: 1  to: (firstNonDigit - 1)) asNumber
  "
  '234Whoopie' initialIntegerOrNil
  'wimpy' initialIntegerOrNil
  '234' initialIntegerOrNil
  '2N' initialIntegerOrNil
  '2' initialIntegerOrNil
  '  89Ten ' initialIntegerOrNil
  '78 92' initialIntegerOrNil
  "
  !

Item was changed:
  ----- Method: String>>sansPeriodSuffix (in category 'converting') -----
  sansPeriodSuffix
  	"Return a copy of the receiver up to, but not including, the first period.  If the receiver's *first* character is a period, then just return the entire receiver. "
  
  	| likely |
  	likely := self copyUpTo: $..
+ 	^ likely size = 0
- 	^ likely size == 0
  		ifTrue:	[self]
  		ifFalse:	[likely]!

Item was changed:
  ----- Method: String>>utf8ToIso (in category 'internet') -----
  utf8ToIso
  	"Only UTF-8 characters that maps to 8-bit ISO-8559-1 values are converted. Others raises an error"
  	| s i c v c2 v2 |
  	s := WriteStream on: (String new: self size).
  	
  	i := 1.
  	[i <= self size] whileTrue: [
  		c := self at: i. i:=i+1.
  		v := c asciiValue.
  		(v > 128)
  			ifFalse: [ s nextPut: c ]
+ 			ifTrue: [((v bitAnd: 252) = 192)
- 			ifTrue: [((v bitAnd: 252) == 192)
  				ifFalse: [self error: 'illegal UTF-8 ISO character']
  				ifTrue: [
  					(i > self size) ifTrue: [ self error: 'illegal end-of-string, expected 2nd byte of UTF-8'].
  					c2 := self at: i. i:=i+1.
  					v2 := c2 asciiValue.
  					((v2 bitAnd: 192) = 128) ifFalse: [self error: 'illegal 2nd UTF-8 char']. 
  					s nextPut: ((v2 bitAnd: 63) bitOr: ((v << 6) bitAnd: 192)) asCharacter]]].
  	^s contents. 
  !

Item was changed:
  ----- Method: Symbol class>>selectorsContaining: (in category 'access') -----
  selectorsContaining: aString
  	"Answer a list of selectors that contain aString within them. Case-insensitive.  Does return symbols that begin with a capital letter."
  
  	| size selectorList ascii |
  
  	selectorList := OrderedCollection new.
  	(size := aString size) = 0 ifTrue: [^selectorList].
  
  	aString size = 1 ifTrue:
  		[
  			ascii := aString first asciiValue.
  			ascii < 128 ifTrue: [selectorList add: (OneCharacterSymbols at: ascii+1)]
  		].
  
  	(aString first isLetter or: [aString first isDigit]) ifFalse:
  		[
+ 			aString size = 2 ifTrue: 
- 			aString size == 2 ifTrue: 
  				[Symbol hasInterned: aString ifTrue:
  					[:s | selectorList add: s]].
  			^selectorList
  		].
  
  	selectorList := selectorList copyFrom: 2 to: selectorList size.
  
  	self allSymbolTablesDo: [:each |
  		each size >= size ifTrue:
  			[(each findSubstring: aString in: each startingAt: 1 
  				matchTable: CaseInsensitiveOrder) > 0
  						ifTrue: [selectorList add: each]]].
  
  	^selectorList reject: [:each | "reject non-selectors, but keep ones that begin with an uppercase"
  		each numArgs < 0 and: [each asString withFirstCharacterDownshifted numArgs < 0]].
  
  "Symbol selectorsContaining: 'scon'"!

Item was changed:
  ----- Method: Symbol>>isInfix (in category 'testing') -----
  isInfix
  	"Answer whether the receiver is an infix message selector."
  
+ 	^ self precedence = 2!
- 	^ self precedence == 2!

Item was changed:
  ----- Method: Symbol>>isKeyword (in category 'testing') -----
  isKeyword
  	"Answer whether the receiver is a message keyword."
  
+ 	^ self precedence = 3!
- 	^ self precedence == 3!

Item was changed:
  ----- Method: Symbol>>isUnary (in category 'testing') -----
  isUnary
  	"Answer whether the receiver is an unary message selector."
  
+ 	^ self precedence = 1!
- 	^ self precedence == 1!



More information about the Packages mailing list