[squeak-dev] The Inbox: Collections-cmm.836.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jun 4 19:34:37 UTC 2019


Chris Muller uploaded a new version of Collections to project The Inbox:
http://source.squeak.org/inbox/Collections-cmm.836.mcz

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

Name: Collections-cmm.836
Author: cmm
Time: 4 June 2019, 2:34:30.820747 pm
UUID: 95d228d9-2fda-4e35-9665-d1daf90cbd99
Ancestors: Collections-cmm.835

- Move utility methods of Collection to 'utilities'.
- #joinSeparatedBy: is useful even for non-SequenceableCollections.
- Speed up String>>#subStrings:.

=============== Diff against Collections-cmm.835 ===============

Item was changed:
+ ----- Method: Collection>>asCommaString (in category 'utilities') -----
- ----- Method: Collection>>asCommaString (in category 'printing') -----
  asCommaString
  	"Return collection printed as 'a, b, c' "
+ 	^ self joinSeparatedBy: ', '!
- 
- 	^String streamContents: [:s | self asStringOn: s delimiter: ', ']
- 		!

Item was changed:
+ ----- Method: Collection>>asCommaStringAnd (in category 'utilities') -----
- ----- Method: Collection>>asCommaStringAnd (in category 'printing') -----
  asCommaStringAnd
  	"Return collection printed as 'a, b and c' "
  
  	^String streamContents: [:s | self asStringOn: s delimiter: ', ' last: ' and ']
  		!

Item was changed:
+ ----- Method: Collection>>asStringOn:delimiter: (in category 'utilities') -----
- ----- Method: Collection>>asStringOn:delimiter: (in category 'printing') -----
  asStringOn: aStream delimiter: delimString
  	"Print elements on a stream separated
  	with a delimiter String like: 'a, b, c'
  	Uses #asString instead of #print:."
  
  	self do: [:elem | aStream nextPutAll: elem asString]
  		separatedBy: [aStream nextPutAll: delimString]!

Item was changed:
+ ----- Method: Collection>>asStringOn:delimiter:last: (in category 'utilities') -----
- ----- Method: Collection>>asStringOn:delimiter:last: (in category 'printing') -----
  asStringOn: aStream delimiter: delimString last: lastDelimString
  	"Print elements on a stream separated
  	with a delimiter between all the elements and with
  	a special one before the last like: 'a, b and c'.
  	Uses #asString instead of #print:
  
  	Note: Feel free to improve the code to detect the last element."
  
  	| n sz |
  	n := 1.
  	sz := self size.
  	self do: [:elem |
  		n := n + 1.
  		aStream nextPutAll: elem asString]
  	separatedBy: [
  		aStream nextPutAll: (n = sz ifTrue: [lastDelimString] ifFalse: [delimString])]!

Item was changed:
+ ----- Method: Collection>>histogramOf: (in category 'utilities') -----
- ----- Method: Collection>>histogramOf: (in category 'converting') -----
  histogramOf: aBlock
  
  	^ self collect: aBlock as: Bag!

Item was added:
+ ----- Method: Collection>>join (in category 'utilities') -----
+ join
+ 	"Example: #(H e l l o W o r l d) join = 'HelloWorld'."
+ 	^ self joinSeparatedBy: String empty!

Item was added:
+ ----- Method: Collection>>joinSeparatedBy: (in category 'utilities') -----
+ joinSeparatedBy: aString
+ 	"Returns a string, which is a concatenation of each element's string representation separated by another string."
+ 	^ String streamContents:
+ 		[ : stream | self asStringOn: stream delimiter: aString ]!

Item was changed:
+ ----- Method: Collection>>topologicallySortedUsing: (in category 'utilities') -----
- ----- Method: Collection>>topologicallySortedUsing: (in category 'converting') -----
  topologicallySortedUsing: aSortBlock 
  	"Answer a SortedCollection whose elements are the elements of the 
  	receiver, but topologically sorted. The topological order is defined 
  	by the argument, aSortBlock."
  
  	| aSortedCollection |
  	aSortedCollection := SortedCollection new: self size.
  	aSortedCollection sortBlock: aSortBlock.
  	self do: [:each | aSortedCollection addLast: each].	"avoids sorting"
  	^ aSortedCollection sortTopologically
  !

Item was removed:
- ----- Method: SequenceableCollection>>join (in category 'converting') -----
- join
- 	"Example: #(H e l l o W o r l d) join = 'HelloWorld'.  "
- 
- 	^ self joinSeparatedBy: ''!

Item was removed:
- ----- Method: SequenceableCollection>>joinSeparatedBy: (in category 'converting') -----
- joinSeparatedBy: aSeparator
- 	"Returns a string, which is a concatenation of each element's string representation separated by another string."
- 
- 	^ String streamContents: [:stream |
- 		self
- 			do: [:ea | stream nextPutAll: ea asString]
- 			separatedBy: [stream nextPutAll: aSeparator asString]]!

Item was changed:
  ----- Method: String>>subStrings: (in category 'converting') -----
  subStrings: separators 
+ 	"Answer an array containing the substrings in the receiver separated by the elements of separators."
- 	"Answer an array containing the substrings in the receiver separated 
- 	by the elements of separators."
  	| char result sourceStream subString |
+ 	(separators isString or:
+ 		[ separators allSatisfy:
+ 			[ : element | element isCharacter ] ]) ifFalse: [ ^ self error: 'separators must be Characters.' ].
- 	#Collectn.
- 	"Changed 2000/04/08 For ANSI <readableString> protocol."
- 	(separators isString or:[separators allSatisfy: [:element | element isCharacter]]) ifFalse:
- 		[^ self error: 'separators must be Characters.'].
  	sourceStream := ReadStream on: self.
  	result := OrderedCollection new.
+ 	subString := WriteStream on: String empty.
+ 	[ sourceStream atEnd ] whileFalse:
+ 		[ char := sourceStream next.
+ 		(separators includes: char)
+ 			ifTrue:
+ 				[ subString isEmpty ifFalse:
+ 					[ result add: subString contents.
+ 					subString resetContents ] ]
+ 			ifFalse: [ subString nextPut: char ] ].
+ 	subString isEmpty ifFalse: [ result add: subString contents ].
- 	subString := String new.
- 	[sourceStream atEnd]
- 		whileFalse: 
- 			[char := sourceStream next.
- 			(separators includes: char)
- 				ifTrue: [subString notEmpty
- 						ifTrue: 
- 							[result add: subString copy.
- 							subString := String new]]
- 				ifFalse: [subString := subString , (String with: char)]].
- 	subString notEmpty ifTrue: [result add: subString copy].
  	^ result asArray!



More information about the Squeak-dev mailing list