[squeak-dev] The Trunk: Collections-ct.1006.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Apr 7 20:59:54 UTC 2022


Christoph Thiede uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-ct.1006.mcz

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

Name: Collections-ct.1006
Author: ct
Time: 7 April 2022, 10:59:36.249279 pm
UUID: cb97907a-6953-f74e-a74f-8d8e16bfca24
Ancestors: Collections-ct.1005, Collections-ct.867, Collections-ct.872, Collections-ct.869, Collections-ct.873, Collections-ct.874, Collections-ct.912, Collections-ct.913, Collections-ct.914, Collections-ct.915, Collections-ct.925, Collections-ct.926, Collections-ct.932, Collections-ct.934

Merge commit. Stills tons of further inbox versions left, but I've enough for today. Friendly reminder that for each version, you can read up the full message in the original version. :-)

Collections-ct.867:
	As requested, attempt to bring different #format: implementations closer together and optimize Text>>#format:.
	
	Revision: Improves documentation and multilingual support.

Collections-ct.869:
	Add clear menu item for Transcript.
	
	Revision: Add multilingual support.

Collections-ct.872:
	Implement #at:ifPresent: on SequenceableCollection.

Collections-ct.873:
	Extends #atLast: protocol on SequenceableCollection by implementing complete ifPresent:Absent: pattern.
	
	Revision: Do not reimplement #atLast:ifAbsent: to avoid slowdowns.

Collections-ct.874:
	Adds constructors for PluggableDictionary and PluggableSet. This is also a useful way to document the aspect that you should not specify an equal block without a hash block.

Collections-ct.912:
	Fixes a typo in two method comments.

Collections-ct.913:
	Adds convenience method for converting text to HTML, #printHtmlOn:breakLines:.

Collections-ct.914:
	Supply start and stop of attributes in Text >> #[removeAttributesThat:][replaceAttributesThat:][by:].
	
	Revision: Improved documentation.

Collections-ct.915:
	Adds accessor and constructor for TextURL.

Collections-ct.925:
	Refines String>>#asPluralBasedOn: to avoid ugly spellings such as 'classs'.

Collections-ct.926:
	Implements missing HTML conversion on TextURL.

Collections-ct.932:
	Fixes a bug in the fallback version of String>>#replaceFrom:to:with:startingAt:. If the replacement contains integers, they should be converted into Characters. See ByteArray>>#asString.

Collections-ct.934:
	Improves multilingual support for errors in collections.

=============== Diff against Collections-ct.1005 ===============

Item was changed:
  ----- Method: Base64MimeConverter>>mimeDecode (in category 'conversion') -----
  mimeDecode
+ 	"Convert a stream in base 64 with only a-z,A-Z,0-9,+,/ to a full byte stream of characters.  Return a whole stream for the user to read."
- 	"Convert a stream in base 64 with only a-z,A-Z,0-9,+,/ to a full byte stream of characters.  Reutrn a whole stream for the user to read."
  
  	| nibA nibB nibC nibD |
  	[mimeStream atEnd] whileFalse: [
  		(nibA := self nextValue) ifNil: [^ dataStream].
  		(nibB := self nextValue) ifNil: [^ dataStream].
  		dataStream nextPut: ((nibA bitShift: 2) + (nibB bitShift: -4)) asCharacter.
  		nibB := nibB bitAnd: 16rF.
  		(nibC := self nextValue) ifNil: [^ dataStream].
  		dataStream nextPut: ((nibB bitShift: 4) + (nibC bitShift: -2)) asCharacter.
  		nibC := nibC bitAnd: 16r3.
  		(nibD := self nextValue) ifNil: [^ dataStream].
  		dataStream nextPut: ((nibC bitShift: 6) + nibD) asCharacter.
  		].
  	^ dataStream!

Item was changed:
  ----- Method: Base64MimeConverter>>mimeDecodeToByteArray (in category 'conversion') -----
  mimeDecodeToByteArray
+ 	"Convert a stream in base 64 with only a-z,A-Z,0-9,+,/ to a full ByteArray of 0-255 values.  Return a whole stream for the user to read."
- 	"Convert a stream in base 64 with only a-z,A-Z,0-9,+,/ to a full ByteArray of 0-255 values.  Reutrn a whole stream for the user to read."
  
  	| nibA nibB nibC nibD |
  	[mimeStream atEnd] whileFalse: [
  		(nibA := self nextValue) ifNil: [^ dataStream].
  		(nibB := self nextValue) ifNil: [^ dataStream].
  		dataStream nextPut: ((nibA bitShift: 2) + (nibB bitShift: -4)).
  		nibB := nibB bitAnd: 16rF.
  		(nibC := self nextValue) ifNil: [^ dataStream].
  		dataStream nextPut: ((nibB bitShift: 4) + (nibC bitShift: -2)).
  		nibC := nibC bitAnd: 16r3.
  		(nibD := self nextValue) ifNil: [^ dataStream].
  		dataStream nextPut: ((nibC bitShift: 6) + nibD).
  		].
  	^ dataStream!

Item was changed:
  ----- Method: Collection>>errorDifferentSize (in category 'private') -----
  errorDifferentSize
  	
+ 	^ self error: 'Other collection must be the same size' translated!
- 	self error: 'otherCollection must be the same size'!

Item was changed:
  ----- Method: Collection>>errorEmptyCollection (in category 'private') -----
  errorEmptyCollection
  
+ 	^ self error: 'This collection is empty' translated!
- 	self error: 'this collection is empty'!

Item was changed:
  ----- Method: Collection>>errorNoMatch (in category 'private') -----
  errorNoMatch
  
+ 	^ self error: 'Collection sizes do not match' translated!
- 	self error: 'collection sizes do not match'!

Item was added:
+ ----- Method: Collection>>name (in category 'printing') -----
+ name
+ 
+ 	^ String streamContents: [:stream |
+ 		self printNameOn: stream]!

Item was changed:
  ----- Method: Dictionary>>errorValueNotFound (in category 'private') -----
  errorValueNotFound
  
+ 	^ self error: 'Value not found' translated!
- 	self error: 'value not found'!

Item was changed:
  ----- Method: HashedCollection>>errorNoFreeSpace (in category 'private') -----
  errorNoFreeSpace
  
+ 	^ self error: 'There is no free space in this collection!!' translated!
- 	self error: 'There is no free space in this collection!!'!

Item was changed:
  ----- Method: KeyNotFound>>messageText (in category 'accessing') -----
  messageText
+ 
+ 	^ messageText ifNil: ['Key not found: {1}' translated format: {self key}]!
- 	"Return a textual description of the exception."
- 	^messageText ifNil:['Key not found: ', key]!

Item was changed:
  ----- Method: NotFound>>messageText (in category 'accessing') -----
  messageText
+ 
+ 	^ messageText ifNil: ['Object is not in the collection.' translated]!
- 	"Return a textual description of the exception."
- 	^messageText ifNil:['Object is not in the collection.']!

Item was changed:
  ----- Method: OrderedCollection>>errorNoSuchElement (in category 'private') -----
  errorNoSuchElement
  
+ 	^ self error: ('Attempt to index a non-existent element in {1}' translated format: {self name})!
- 	self error: (String streamContents: [ :stream | 
- 		stream nextPutAll: 'attempt to index a non-existent element in '.
- 		self printNameOn: stream ])!

Item was changed:
  ----- Method: OrderedCollection>>errorNotEnoughElements (in category 'private') -----
  errorNotEnoughElements
  
+ 	^ self error: ('Attempt to remove more elements than possible from {1}' translated format: {self name})!
- 	self error: (String streamContents: [ :stream | 
- 		stream nextPutAll: 'attempt to remove more elements than possible from '.
- 		self printNameOn: stream ])!

Item was added:
+ ----- Method: PluggableDictionary class>>hashBlock: (in category 'instance creation') -----
+ hashBlock: aHashBlock
+ 
+ 	^ self new
+ 		hashBlock: aHashBlock;
+ 		yourself!

Item was added:
+ ----- Method: PluggableDictionary class>>hashBlock:equalBlock: (in category 'instance creation') -----
+ hashBlock: aHashBlock equalBlock: anEqualBlock
+ 
+ 	^ self new
+ 		hashBlock: aHashBlock;
+ 		equalBlock: anEqualBlock;
+ 		yourself!

Item was added:
+ ----- Method: PluggableSet class>>hashBlock: (in category 'instance creation') -----
+ hashBlock: aHashBlock
+ 
+ 	^ self new
+ 		hashBlock: aHashBlock;
+ 		yourself!

Item was added:
+ ----- Method: PluggableSet class>>hashBlock:equalBlock: (in category 'instance creation') -----
+ hashBlock: aHashBlock equalBlock: anEqualBlock
+ 
+ 	^ self new
+ 		hashBlock: aHashBlock;
+ 		equalBlock: anEqualBlock;
+ 		yourself!

Item was added:
+ ----- Method: SequenceableCollection>>at:ifPresent: (in category 'accessing') -----
+ at: index ifPresent: aBlock
+ 
+ 	^ self at: index ifPresent: aBlock ifAbsent: []!

Item was added:
+ ----- Method: SequenceableCollection>>atLast:ifPresent: (in category 'accessing') -----
+ atLast: indexFromEnd ifPresent: elementBlock
+ 
+ 	^ self
+ 		at: self size + 1 - indexFromEnd
+ 		ifPresent: elementBlock
+ 		ifAbsent: []!

Item was added:
+ ----- Method: SequenceableCollection>>atLast:ifPresent:ifAbsent: (in category 'accessing') -----
+ atLast: indexFromEnd ifPresent: elementBlock ifAbsent: exceptionBlock
+ 	"Answer the value of elementBlock on the element at indexFromEnd from the last position. If the receiver does not contain an element at this position, answer the result of evaluating exceptionBlock."
+ 
+ 	^ self
+ 		at: self size + 1 - indexFromEnd
+ 		ifPresent: elementBlock
+ 		ifAbsent: exceptionBlock!

Item was changed:
  ----- Method: SequenceableCollection>>errorFirstObject: (in category 'private') -----
  errorFirstObject: anObject
+ 
+ 	^ self error: 'Specified object is first object' translated!
- 	self error: 'specified object is first object'!

Item was changed:
  ----- Method: SequenceableCollection>>errorLastObject: (in category 'private') -----
  errorLastObject: anObject
+ 
+ 	^ self error: 'Specified object is last object' translated!
- 	self error: 'specified object is last object'!

Item was changed:
  ----- Method: SequenceableCollection>>errorOutOfBounds (in category 'private') -----
  errorOutOfBounds
  
+ 	^ self error: 'Indices are out of bounds' translated!
- 	self error: 'indices are out of bounds'!

Item was changed:
  ----- Method: String>>asPluralBasedOn: (in category 'converting') -----
  asPluralBasedOn: aNumberOrCollection
  	"Append an 's' to this string based on whether aNumberOrCollection is 1 or of size 1."
  
+ 	aNumberOrCollection = 1
+ 		ifTrue: [^ self].
+ 	(aNumberOrCollection isCollection and: [aNumberOrCollection size = 1])
+ 		ifTrue: [^ self].
+ 	
+ 	^ (self endsWith: 's')
+ 		ifTrue: [self , 'es']
+ 		ifFalse: [self , 's']
- 	^ (aNumberOrCollection = 1 or:
- 		[aNumberOrCollection isCollection and: [aNumberOrCollection size = 1]])
- 			ifTrue: [self]
- 			ifFalse: [self, 's']
  !

Item was changed:
  ----- Method: String>>format: (in category 'formatting') -----
+ format: arguments 
+ 	"Format the receiver with arguments.
+ 	
+ 	Simplest example:
+ 		'foo {1} bar' format: {Date today}.
+ 	
+ 	Complete example:
+ 		'\{ \} \\ foo {1} bar {2}' format: {12. 'string'}.
- format: aCollection 
- 	"format the receiver with aCollection  
- 	 
- 	simplest example:  
- 	'foo {1} bar' format: {Date today}.
- 	 
- 	complete example:  
- 	'\{ \} \\ foo {1} bar {2}' format: {12. 'string'}. 
  	"
+ 	^ self class new: self size * 11 // 10 "+10%" streamContents: [ :output |
- 	^self class new: self size * 11 // 10 "+10%" streamContents: [ :output |
  		| lastIndex nextIndex |
  		lastIndex := 1.
  		[ (nextIndex := self indexOfAnyOf: FormatCharacterSet startingAt: lastIndex) = 0 ] whileFalse: [
  			nextIndex = lastIndex ifFalse: [
  				output next: nextIndex - lastIndex putAll: self startingAt: lastIndex ].
+ 			(self at: nextIndex) caseOf: {
+ 				[ $\ ] -> [ output nextPut: (self at: (nextIndex := nextIndex + 1)) ].
+ 				[ ${ ] -> [
- 			(self at: nextIndex) == $\
- 				ifTrue: [ output nextPut: (self at: (nextIndex := nextIndex + 1)) ]
- 				ifFalse: [ "${"
  					"Parse the index - a positive integer in base 10."
  					| digitValue collectionIndex |
  					collectionIndex := 0.
  					[ (digitValue := self basicAt: (nextIndex := nextIndex + 1)) between: 48 "$0 asciiValue" and: 57 "$9 asciiValue" ] whileTrue: [
+ 						collectionIndex := collectionIndex * 10 + digitValue - 48 "$0 asciiValue". ].
+ 					digitValue =  125 "$} asciiValue" ifFalse: [ self error: ('{1} expected' translated format: {$}}) ].
+ 					output nextPutAll: (arguments at: collectionIndex) asString ] }.
- 						collectionIndex := collectionIndex * 10 + digitValue - 48. "$0 asciiValue" ].
- 					digitValue =  125 "$} asciiValue" ifFalse: [ self error: '$} expected' ].
- 					output nextPutAll: (aCollection at: collectionIndex) asString ].
  			lastIndex := nextIndex + 1 ].
  		lastIndex <= self size ifTrue: [
  			output next: self size - lastIndex + 1 putAll: self startingAt: lastIndex ] ]!

Item was changed:
  ----- Method: String>>replaceFrom:to:with:startingAt: (in category 'private') -----
  replaceFrom: start to: stop with: replacement startingAt: repStart 
  	"Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
  	<primitive: 105>
+ 	| index repOff |
+ 	repOff := repStart - start.
+ 	index := start - 1.
+ 	[(index := index + 1) <= stop]
+ 		whileTrue: [self at: index put: (replacement at: repOff + index) asCharacter].!
- 	super replaceFrom: start to: stop with: replacement startingAt: repStart!

Item was changed:
  ----- Method: Text>>format: (in category 'formatting') -----
  format: arguments 
+ 	"Format the receiver with arguments, respecting the attributes in both receiver and all collection elements that are texts.
- 	"format the receiver with arguments, respecting the format both of receiver and collection elements"
  	
+ 	Complete example:
+ 		'\{ \} \\ <b>foo {1}</b> <u>bar {2}</u>' asTextFromHtml format: {12. 't<i>ex</i>t' asTextFromHtml}.
+ 	"
+ 	
+ 	^ self class new: self size * 11 // 10 "+10%" streamContents: [ :output |
- 	^self class new: self size * 11 // 10 streamContents: [ :output |
  		| nextIndex |
  		nextIndex := 1.
  		[ nextIndex <= self size ] whileTrue: [
  			(self at: nextIndex) caseOf: {
+ 				[ $\ ] -> [
- 				[$\] -> [
  					nextIndex := nextIndex + 1.
  					output withAttributes: (runs at: nextIndex) do: [
  						output nextPut: (self at: nextIndex) ] ].
+ 				[ ${ ] -> [
- 				[${] -> [
  					"Parse the index - a positive integer in base 10."
+ 					| digitValue collectionIndex attributes |
- 					| character collectionIndex attributes |
  					collectionIndex := 0.
  					attributes := Set new.
+ 					[ (digitValue := string basicAt: (nextIndex := nextIndex + 1)) between: 48 "$0 asciiValue" and: 57 "$9 asciiValue" ] whileTrue: [
+ 						collectionIndex := collectionIndex * 10 + digitValue - 48 "$0 asciiValue". 
- 					[ (character := string at: (nextIndex := nextIndex + 1)) isDigit ] whileTrue: [
- 						collectionIndex := collectionIndex * 10 + character digitValue.
  						attributes addAll: (runs at: nextIndex) ].
+ 					digitValue = 125 "$} asciiValue" ifFalse: [ self error: ('{1} expected' translated format: {$}}) ].
- 					character = $} ifFalse: [ self error: '$} expected' ].
  					output withAttributes: attributes do: [
  						output nextPutAll: (arguments at: collectionIndex) asStringOrText ] ] }
  				otherwise: [
  					output withAttributes: (runs at: nextIndex) do: [
  						output nextPut: (self at: nextIndex) ] ].
  			nextIndex := nextIndex + 1 ] ]!

Item was changed:
  ----- Method: Text>>printHtmlOn: (in category 'html') -----
+ printHtmlOn: aStream
+ 
+ 	^ self
+ 		printHtmlOn: aStream
+ 		breakLines: true!
- printHtmlOn: aStream 
- 	
- 	(HtmlReadWriter on: aStream)
- 		nextPutText: self.!

Item was added:
+ ----- Method: Text>>printHtmlOn:breakLines: (in category 'html') -----
+ printHtmlOn: aStream breakLines: aBoolean
+ 
+ 	(HtmlReadWriter on: aStream)
+ 		breakLines: aBoolean;
+ 		nextPutText: self.!

Item was changed:
  ----- Method: Text>>removeAttributesThat:replaceAttributesThat:by: (in category 'converting') -----
  removeAttributesThat: removalBlock replaceAttributesThat: replaceBlock by: convertBlock
+ 	"Enumerate all attributes in the receiver. Remove those passing removalBlock and replace those passing replaceBlock after converting it through convertBlock. All blocks may also accept a second and third argument indicating the start and stop positions of the current attribute."
- 	"Enumerate all attributes in the receiver. Remove those passing removalBlock and replace those passing replaceBlock after converting it through convertBlock"
  	| added removed |
  	"Deliberately optimized for the no-op default."
  	added := removed := nil.
  	runs withStartStopAndValueDo: [ :start :stop :attribs | 
  		attribs do: [ :attrib | | new |
+ 			(removalBlock cull: attrib cull: start cull: stop) ifTrue:[
- 			(removalBlock value: attrib) ifTrue:[
  				removed ifNil:[removed := WriteStream on: #()].
  				removed nextPut: {start. stop. attrib}.
  			] ifFalse:[
+ 				(replaceBlock cull: attrib cull: start cull: stop) ifTrue:[
- 				(replaceBlock value: attrib) ifTrue:[
  					removed ifNil:[removed := WriteStream on: #()].
  					removed nextPut: {start. stop. attrib}.
+ 					new := convertBlock cull: attrib cull: start cull: stop.
- 					new := convertBlock value: attrib.
  					added ifNil:[added := WriteStream on: #()].
  					added nextPut: {start. stop. new}.
  				].
  			].
  		].
  	].
  	(added == nil and:[removed == nil]) ifTrue:[^self].
  	"otherwise do the real work"
  	removed ifNotNil:[removed contents do:[:spec|
  		self removeAttribute: spec last from: spec first to: spec second]].
  	added ifNotNil:[added contents do:[:spec|
  		self addAttribute: spec last from: spec first to: spec second]].!

Item was added:
+ ----- Method: TextURL class>>url: (in category 'instance creation') -----
+ url: anUrl
+ 
+ 	^ self new
+ 		url: anUrl;
+ 		yourself!

Item was added:
+ ----- Method: TextURL>>closeHtmlOn: (in category 'html') -----
+ closeHtmlOn: aStream
+ 
+ 	aStream nextPutAll: '</a>'.!

Item was added:
+ ----- Method: TextURL>>openHtmlOn: (in category 'html') -----
+ openHtmlOn: aStream
+ 
+ 	aStream
+ 		nextPutAll: '<a href="';
+ 		nextPutAll: self url;
+ 		nextPutAll: '">'.!

Item was added:
+ ----- Method: TextURL>>url (in category 'accessing') -----
+ url
+ 	^ url!

Item was changed:
  ----- Method: TranscriptStream>>addModelItemsToWindowMenu: (in category 'menu') -----
  addModelItemsToWindowMenu: aMenu 
  	
  	aMenu addLine.
  	aMenu
+ 		add: 'clear' translated
- 		add: 'clear'
  		target: self
  		action: #clear.!



More information about the Squeak-dev mailing list