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

commits at source.squeak.org commits at source.squeak.org
Mon Feb 27 00:56:16 UTC 2017


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

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

Name: Collections-ul.738
Author: ul
Time: 27 February 2017, 12:50:24.923499 am
UUID: 3cdaac93-5a62-4fb6-8037-4323767c63a1
Ancestors: Collections-ul.737

Part #3 of Improve SequenceableCollection's index-related search methods

- fixed typo in #indexOf:startingAt:ifAbsent:
- trimmed unnecessary #ifAbsent: sends
- improved a few methods

=============== Diff against Collections-ul.737 ===============

Item was changed:
  ----- Method: ByteString>>substrings (in category 'converting') -----
  substrings
  	"Answer an array of the substrings that compose the receiver."
+ 	
+ 	^Array streamContents: [ :stream |
+ 		| end start |
+ 		end := 1.
+ 		"find one substring each time through this loop"
+ 		[ "find the beginning of the next substring"
+ 			(start := self 
+ 				indexOfAnyOf: CharacterSet nonSeparators 
+ 				startingAt: end) = 0 ]
+ 			whileFalse: [
+ 				"find the end"
+ 				end := self 
+ 					indexOfAnyOf: CharacterSet separators 
+ 					startingAt: start
+ 					ifAbsent: [ self size + 1 ].
+ 				stream nextPut: (self copyFrom: start to: end - 1) ] ]!
- 	| result end beginning |
- 	result := WriteStream on: (Array new: 10).
- 	end := 0.
- 	"find one substring each time through this loop"
- 	[ "find the beginning of the next substring"
- 	beginning := self indexOfAnyOf: CharacterSet nonSeparators 
- 							startingAt: end+1 ifAbsent: [ nil ].
- 	beginning ~~ nil ] whileTrue: [
- 		"find the end"
- 		end := self indexOfAnyOf: CharacterSet separators 
- 					startingAt: beginning ifAbsent: [ self size + 1 ].
- 		end := end - 1.
- 		result nextPut: (self copyFrom: beginning to: end).
- 	].
- 	^result contents!

Item was changed:
  ----- Method: RWBinaryOrTextStream>>upTo: (in category 'accessing') -----
  upTo: anObject
  	"fast version using indexOf:"
  
  	| start end |
- 	start := position+1.
  	isBinary
  		ifTrue: [ anObject isInteger ifFalse: [ ^self upToEnd ] ]
  		ifFalse: [ anObject isCharacter ifFalse: [ ^self upToEnd ] ].
+ 	start := position + 1.
+ 	end := collection indexOf: anObject asCharacter startingAt: start.
- 	end := collection indexOf: anObject asCharacter startingAt: start ifAbsent: [ 0 ].
  	"not present--return rest of the collection"	
  	(end = 0 or: [end > readLimit]) ifTrue: [ ^self upToEnd ].
  	"skip to the end and return the data passed over"
  	position := end.
  	^((isBinary ifTrue: [ ByteArray ] ifFalse: [ String ]) new: end - start)
  		replaceFrom: 1
  		to: end - start
  		with: collection
  		startingAt: start!

Item was changed:
  ----- Method: ReadStream>>upToAnyOf:do: (in category 'accessing') -----
  upToAnyOf: aCollection do: aBlock
  	"Overriden for speed"
  	| end result |
+ 	end := collection indexOfAnyOf: aCollection startingAt: 1 + position.
- 	end := collection indexOfAnyOf: aCollection startingAt: 1 + position ifAbsent: [0].
  	(end = 0 or: [end > readLimit]) ifTrue: [^self upToEnd].
  	result := collection copyFrom: 1 + position to: -1 + end.
  	position := end.
  	aBlock value: (collection at: end).
  	^result!

Item was changed:
  ----- Method: SequenceableCollection>>indexOf:startingAt:ifAbsent: (in category 'accessing') -----
  indexOf: anElement startingAt: start ifAbsent: exceptionBlock
  	"Answer the index of the first occurence of anElement after start
  	within the receiver. If the receiver does not contain anElement, 
  	answer the 	result of evaluating the argument, exceptionBlock."
  
  	| index |
+ 	(index := self indexOf: anElement startingAt: start) = 0 ifFalse: [ ^index ].
- 	(index := self indexOf: start startingAt: start) = 0 ifFalse: [ ^index ].
  	^exceptionBlock value!

Item was changed:
  ----- Method: String>>withBlanksTrimmed (in category 'converting') -----
  withBlanksTrimmed
  	"Return a copy of the receiver from which leading and trailing blanks have been trimmed."
  
  	| first last |
+ 	first := self indexOfAnyOf: CharacterSet nonSeparators startingAt: 1.
- 	first := self indexOfAnyOf: CharacterSet nonSeparators startingAt: 1 ifAbsent: [0].
  	first = 0 ifTrue: [ ^'' ].  "no non-separator character"
  	last := self lastIndexOfAnyOf: CharacterSet nonSeparators startingAt: self size ifAbsent: [self size].
  	(first = 1 and: [ last = self size ]) ifTrue: [ ^self copy ].
  	^self
  		copyFrom: first
  		to: last
  !



More information about the Squeak-dev mailing list