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

commits at source.squeak.org commits at source.squeak.org
Sat Aug 27 17:24:17 UTC 2016


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

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

Name: Collections-ul.714
Author: ul
Time: 24 August 2016, 9:22:59.948045 pm
UUID: 88200af6-48e5-4ae3-a247-a0b5a74985bf
Ancestors: Collections-mt.713

SequenceableCollection>>copyReplaceAll:with:asTokens:
- return a copy in all cases
- avoid quadratic performance when many replacements have to be done

AttributedTextStream:
- avoid creation of unnecessary objects during initialization
- use default size 10

Don't let #next:putAll:startingAt: roll back the receiver when the first argument is negative.

=============== Diff against Collections-mt.713 ===============

Item was changed:
  SystemOrganization addCategory: #'Collections-Abstract'!
  SystemOrganization addCategory: #'Collections-Arrayed'!
  SystemOrganization addCategory: #'Collections-Cache'!
  SystemOrganization addCategory: #'Collections-Exceptions'!
+ SystemOrganization addCategory: #'Collections-Heap'!
  SystemOrganization addCategory: #'Collections-Sequenceable'!
  SystemOrganization addCategory: #'Collections-Stack'!
  SystemOrganization addCategory: #'Collections-Streams'!
  SystemOrganization addCategory: #'Collections-Strings'!
  SystemOrganization addCategory: #'Collections-Support'!
  SystemOrganization addCategory: #'Collections-Text'!
  SystemOrganization addCategory: #'Collections-Unordered'!
  SystemOrganization addCategory: #'Collections-Weak'!
- SystemOrganization addCategory: #'Collections-Heap'!

Item was changed:
  ----- Method: AttributedTextStream class>>new (in category 'instance creation') -----
  new
  	"For this class we override Stream class>>new since this
  	class actually is created using #new, even though it is a Stream."
  	
+ 	^self new: 10!
- 	^self basicNew initialize!

Item was added:
+ ----- Method: AttributedTextStream class>>new: (in category 'instance creation') -----
+ new: n
+ 	
+ 	^self basicNew 
+ 		initialize: n;
+ 		yourself!

Item was removed:
- ----- Method: AttributedTextStream>>initialize (in category 'initialize-release') -----
- initialize
- 
- 	characters := String new writeStream.
- 	currentAttributes := #().
- 	currentRun := 0.
- 	attributeValues := (Array new: 50) writeStream.
- 	attributeRuns := (Array new: 50) writeStream!

Item was added:
+ ----- Method: AttributedTextStream>>initialize: (in category 'initialize-release') -----
+ initialize: n
+ 
+ 	super initialize.
+ 	characters := (String new: n) writeStream.
+ 	currentAttributes := #().
+ 	currentRun := 0.
+ 	attributeValues := (Array new: (n min: 10)) writeStream.
+ 	attributeRuns := (Array new: (n min: 10)) writeStream!

Item was added:
+ ----- Method: AttributedTextStream>>next:putAll:startingAt: (in category 'accessing') -----
+ next: anInteger putAll: aString startingAt: startIndex
+ 
+ 	"add an entire string with the same attributes"
+ 	anInteger > 0 ifFalse: [ ^aString ].
+ 	currentRun := currentRun + anInteger.
+ 	^characters 
+ 		next: anInteger
+ 		putAll: aString
+ 		startingAt: startIndex!

Item was changed:
  ----- Method: NullStream>>next:putAll:startingAt: (in category 'writing') -----
  next: anInteger putAll: aCollection startingAt: startIndex
  	"Store the next anInteger elements from the given collection."
  
+ 	anInteger > 0 ifFalse: [ ^aCollection ].
  	position := position + anInteger.
  	^aCollection!

Item was changed:
  ----- Method: SequenceableCollection>>copyReplaceAll:with:asTokens: (in category 'private') -----
  copyReplaceAll: oldSubstring with: newSubstring asTokens: ifTokens
  	"Answer a copy of the receiver in which all occurrences of
  	oldSubstring have been replaced by newSubstring.
  	ifTokens (valid for Strings only) specifies that the characters
  	surrounding the recplacement must not be alphanumeric.
  		Bruce Simth,  must be incremented by 1 and not 
  	newSubstring if ifTokens is true.  See example below. "
  
+ 	| currentIndex |
+ 	(ifTokens and: [ self isString not and: [ self isText not ] ]) ifTrue: [
+ 		self error: 'Token replacement only valid for Strings' ].
+ 	(currentIndex := self indexOfSubCollection: oldSubstring startingAt: 1 ifAbsent: 0) = 0 ifTrue: [ ^self copy ].
+ 	oldSubstring size = newSubstring size ifTrue: [ "Special case"
+ 		| string startSearch endIndex |
+ 		string := self copy.
+ 		startSearch := 1.
+ 		[
+ 			endIndex := currentIndex + oldSubstring size - 1.
+ 			(ifTokens and: [
+ 				(currentIndex > 1 and: [ (self at: currentIndex - 1) isAlphaNumeric ])
+ 					or: [ endIndex < self size and: [ (self at: endIndex + 1) isAlphaNumeric ] ] ])
+ 				ifFalse: [ "match"
+ 					string
+ 						replaceFrom: currentIndex
+ 						to: endIndex
+ 						with: newSubstring
+ 						startingAt: 1 ].
+ 			startSearch := endIndex + 1.
+ 			(currentIndex := self indexOfSubCollection: oldSubstring startingAt: startSearch ifAbsent: 0) = 0 ] whileFalse.
+ 		^string ].
+ 	^self species new: self size streamContents: [ :stream |
+ 		| startSearch endIndex |
+ 		startSearch := 1.
+ 		[
+ 			endIndex := currentIndex + oldSubstring size - 1.
+ 			(ifTokens and: [
+ 				(currentIndex > 1 and: [ (self at: currentIndex - 1) isAlphaNumeric ])
+ 					or: [ endIndex < self size and: [ (self at: endIndex + 1) isAlphaNumeric ] ] ])
+ 				ifFalse: [ "match"
+ 					stream
+ 						next: currentIndex - startSearch
+ 							putAll: self
+ 							startingAt: startSearch;
+ 						nextPutAll: newSubstring ]
+ 				ifTrue: [
+ 					stream
+ 						next: currentIndex - startSearch + oldSubstring size
+ 						putAll: self
+ 						startingAt: startSearch ].
+ 			startSearch := endIndex + 1.
+ 			(currentIndex := self indexOfSubCollection: oldSubstring startingAt: startSearch ifAbsent: 0) = 0 ] whileFalse.
+ 		stream
+ 			next: self size - startSearch + 1
+ 			putAll: self
+ 			startingAt: startSearch ]
- 	| aString startSearch currentIndex endIndex |
- 	(ifTokens and: [(self isString) not])
- 		ifTrue: [(self isKindOf: Text) ifFalse: [
- 			self error: 'Token replacement only valid for Strings']].
- 	aString := self.
- 	startSearch := 1.
- 	[(currentIndex := aString indexOfSubCollection: oldSubstring startingAt: startSearch)
- 			 > 0]
- 		whileTrue: 
- 		[endIndex := currentIndex + oldSubstring size - 1.
- 		(ifTokens not
- 			or: [(currentIndex = 1
- 					or: [(aString at: currentIndex-1) isAlphaNumeric not])
- 				and: [endIndex = aString size
- 					or: [(aString at: endIndex+1) isAlphaNumeric not]]])
- 			ifTrue: [aString := aString
- 					copyReplaceFrom: currentIndex
- 					to: endIndex
- 					with: newSubstring.
- 				startSearch := currentIndex + newSubstring size]
- 			ifFalse: [
- 				ifTokens 
- 					ifTrue: [startSearch := currentIndex + 1]
- 					ifFalse: [startSearch := currentIndex + newSubstring size]]].
- 	^ aString
  
  "Test case:
+ 	'test te string' copyReplaceAll: 'te' with: 'longone' asTokens: true   "!
- 	'test te string' copyReplaceAll: 'te' with: 'longone' asTokens: true   "
- !

Item was changed:
  ----- Method: WriteStream>>next:putAll:startingAt: (in category 'accessing') -----
  next: anInteger putAll: aCollection startingAt: startIndex
  	"Store the next anInteger elements from the given collection."
  
  	| newEnd |
+ 	anInteger > 0 ifFalse: [ ^aCollection ].
  	(collection class == aCollection class
  		or: [ collection isString 
  			and: [ aCollection isString
  			and: [ collection class format = aCollection class format ] ] ]) "Let Strings with the same field size as collection take the quick route too."
  		ifFalse: [ ^super next: anInteger putAll: aCollection startingAt: startIndex ].
  
  	newEnd := position + anInteger.
  	newEnd > writeLimit ifTrue:
  		[self growTo: newEnd + 10].
  
  	collection replaceFrom: position+1 to: newEnd  with: aCollection startingAt: startIndex.
  	position := newEnd.
  
  	^aCollection!



More information about the Squeak-dev mailing list