[squeak-dev] The Trunk: Collections-nice.206.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Nov 22 17:28:25 UTC 2009


Nicolas Cellier uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-nice.206.mcz

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

Name: Collections-nice.206
Author: nice
Time: 22 November 2009, 6:28:03 am
UUID: 53a79cf1-f758-47e4-9bdd-589e86cc5de7
Ancestors: Collections-ar.205, Collections-ul.205

1) merge ul.205 (collect:into: collect:as:)
2) correct #nextLine and #upToAnyOf: using a new message #collectionSpecies

=============== Diff against Collections-ar.205 ===============

Item was changed:
  ----- Method: PositionableStream>>nextLine (in category 'accessing') -----
  nextLine
+ 	"Answer next line (may be empty), or nil if at end.
+ 	Handle a zoo of line delimiters CR, LF, or CR-LF pair"
- 	"Answer next line (may be empty), or nil if at end"
  
+ 	| newStream element crlf |
  	self atEnd ifTrue: [^nil].
+ 	crlf := CharacterSet crlf.
+ 	newStream := WriteStream on: (self collectionSpecies new: 100).
+ 	[self atEnd ifTrue: [^newStream contents].
+ 	crlf includes: (element := self next)]
+ 		whileFalse: [newStream nextPut: element].
+ 	element = Character cr ifTrue: [self peekFor: Character lf]. "handle an eventual CR LF pair"
+ 	^newStream contents!
- 	^self upTo: Character cr!

Item was added:
+ ----- Method: PositionableStream>>collectionSpecies (in category 'private') -----
+ collectionSpecies
+ 	"Answer the species of collection into which the receiver can stream"
+ 	
+ 	^collection species!

Item was changed:
  ----- Method: PositionableStream>>next: (in category 'accessing') -----
  next: anInteger 
  	"Answer the next anInteger elements of my collection. Must override 
  	because default uses self contents species, which might involve a large 
  	collection."
  
  	| newArray |
+ 	newArray := self collectionSpecies new: anInteger.
- 	newArray := collection species new: anInteger.
  	1 to: anInteger do: [:index | newArray at: index put: self next].
  	^newArray!

Item was added:
+ ----- Method: Collection>>fillFrom:with: (in category 'private') -----
+ fillFrom: aCollection with: aBlock
+ 	"Evaluate aBlock with each of aCollections's elements as the argument.  
+ 	Collect the resulting values into self. Answer self."
+ 
+ 	aCollection do: [ :each |
+ 		self add: (aBlock value: each) ]!

Item was added:
+ ----- Method: ArrayedCollection>>fillFrom:with: (in category 'private') -----
+ fillFrom: aCollection with: aBlock
+ 	"Evaluate aBlock with each of aCollections's elements as the argument.  
+ 	Collect the resulting values into self. Answer self."
+ 
+ 	| index |
+ 	index := 0.
+ 	aCollection do: [ :each |
+ 		self at: (index := index + 1) put: (aBlock value: each) ]!

Item was changed:
  ----- Method: PositionableStream>>upTo: (in category 'accessing') -----
  upTo: anObject 
  	"Answer a subcollection from the current access position to the 
  	occurrence (if any, but not inclusive) of anObject in the receiver. If 
  	anObject is not in the collection, answer the entire rest of the receiver."
  	| newStream element |
+ 	newStream := WriteStream on: (self collectionSpecies new: 100).
- 	newStream := WriteStream on: (collection species new: 100).
  	[self atEnd or: [(element := self next) = anObject]]
  		whileFalse: [newStream nextPut: element].
  	^newStream contents!

Item was added:
+ ----- Method: Collection>>collect:as: (in category 'enumerating') -----
+ collect: aBlock as: aClass
+ 	"Evaluate aBlock with each of the receiver's elements as the argument.  
+ 	Collect the resulting values into an instance of aClass. Answer the resulting collection."
+ 
+ 	^(aClass new: self size) fillFrom: self with: aBlock!

Item was changed:
  ----- Method: PositionableStream>>upToAnyOf: (in category 'accessing') -----
  upToAnyOf: aCollection 
  	"Answer a subcollection from the current access position to the 
  	occurrence (if any, but not inclusive) of any object in the collection. If 
  	no matching object is found, answer the entire rest of the receiver."
  	| newStream element |
+ 	newStream := WriteStream on: (self collectionSpecies new: 100).
- 	newStream := WriteStream on: (collection species new: 100).
  	[self atEnd or: [aCollection includes: (element := self next)]]
  		whileFalse: [newStream nextPut: element].
  	^newStream contents!

Item was added:
+ ----- Method: Dictionary>>fillFrom:with: (in category 'private') -----
+ fillFrom: aCollection with: aBlock
+ 	"Evaluate aBlock with each of aCollections's elements as the argument.  
+ 	Collect the resulting values into self. Answer self."
+ 
+ 	aCollection keysAndValuesDo: [ :key :value |
+ 		self at: key put: (aBlock value: value) ]!

Item was added:
+ ----- Method: Collection>>collect:into: (in category 'enumerating') -----
+ collect: aBlock into: aCollection
+ 	"Evaluate aBlock with each of the receiver's elements as the argument.  
+ 	Collect the resulting values into aCollection. Answer aCollection."
+ 
+ 	^aCollection fillFrom: self with: aBlock!

Item was changed:
  ----- Method: PositionableStream>>upToEnd (in category 'accessing') -----
  upToEnd
  	"Answer a subcollection from the current access position through the last element of the receiver."
  
  	| newStream |
+ 	newStream := WriteStream on: (self collectionSpecies new: 100).
- 	newStream := WriteStream on: (collection species new: 100).
  	[self atEnd] whileFalse: [ newStream nextPut: self next ].
  	^ newStream contents!




More information about the Squeak-dev mailing list