[squeak-dev] The Trunk: Collections-bf.588.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Dec 8 00:30:45 UTC 2014


Bert Freudenberg uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-bf.588.mcz

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

Name: Collections-bf.588
Author: bf
Time: 8 December 2014, 1:30:10.896 am
UUID: fa77c95e-6dc5-4ae1-acdc-2d1478d62476
Ancestors: Collections-ul.587

Restore timestamps lost in assignment conversion.

=============== Diff against Collections-ul.587 ===============

Item was changed:
  ----- Method: Set>>occurrencesOf: (in category 'testing') -----
  occurrencesOf: anObject 
  	^ (self includes: anObject) ifTrue: [1] ifFalse: [0]!

Item was changed:
  ----- Method: String class>>cr (in category 'instance creation') -----
  cr
  	"Answer a string containing a single carriage return character."
  
  	^ self with: Character cr
  !

Item was changed:
  ----- Method: String class>>crlf (in category 'instance creation') -----
  crlf
  	"Answer a string containing a carriage return and a linefeed."
  
  	^ self with: Character cr with: Character lf
  !

Item was changed:
  ----- Method: String class>>fromByteArray: (in category 'instance creation') -----
  fromByteArray: aByteArray
  
  	^ aByteArray asString
  !

Item was changed:
  ----- Method: String class>>fromString: (in category 'instance creation') -----
  fromString: aString 
  	"Answer an instance of me that is a copy of the argument, aString."
  	
  	^ aString copyFrom: 1 to: aString size!

Item was changed:
  ----- Method: String class>>tab (in category 'instance creation') -----
  tab
  	"Answer a string containing a single tab character."
  
  	^ self with: Character tab
  !

Item was changed:
  ----- Method: String>>* (in category 'arithmetic') -----
  * arg
  
  	^ arg adaptToString: self andSend: #*!

Item was changed:
  ----- Method: String>>+ (in category 'arithmetic') -----
  + arg
  
  	^ arg adaptToString: self andSend: #+!

Item was changed:
  ----- Method: String>>- (in category 'arithmetic') -----
  - arg
  
  	^ arg adaptToString: self andSend: #-!

Item was changed:
  ----- Method: String>>/ (in category 'arithmetic') -----
  / arg
  
  	^ arg adaptToString: self andSend: #/!

Item was changed:
  ----- Method: String>>// (in category 'arithmetic') -----
  // arg
  
  	^ arg adaptToString: self andSend: #//!

Item was changed:
  ----- Method: String>>< (in category 'comparing') -----
  < aString 
  	"Answer whether the receiver sorts before aString.
  	The collation order is simple ascii (with case differences)."
  
  	^ (self compare: self with: aString collated: AsciiOrder) = 1!

Item was changed:
  ----- Method: String>>> (in category 'comparing') -----
  > aString 
  	"Answer whether the receiver sorts after aString.
  	The collation order is simple ascii (with case differences)."
  
  	^ (self compare: self with: aString collated: AsciiOrder) = 3!

Item was changed:
  ----- Method: String>>>= (in category 'comparing') -----
  >= aString 
  	"Answer whether the receiver sorts after or equal to aString.
  	The collation order is simple ascii (with case differences)."
  
  	^ (self compare: self with: aString collated: AsciiOrder) >= 2!

Item was changed:
  ----- Method: String>>\\ (in category 'arithmetic') -----
  \\ arg
  
  	^ arg adaptToString: self andSend: #\\!

Item was changed:
  ----- Method: String>>adaptToCollection:andSend: (in category 'converting') -----
  adaptToCollection: rcvr andSend: selector
  	"If I am involved in arithmetic with a collection, convert me to a number."
  
  	^ rcvr perform: selector with: self asNumber!

Item was changed:
  ----- Method: String>>adaptToNumber:andSend: (in category 'converting') -----
  adaptToNumber: rcvr andSend: selector
  	"If I am involved in arithmetic with a number, convert me to a number."
  
  	^ rcvr perform: selector with: self asNumber!

Item was changed:
  ----- Method: String>>adaptToPoint:andSend: (in category 'converting') -----
  adaptToPoint: rcvr andSend: selector
  	"If I am involved in arithmetic with a point, convert me to a number."
  
  	^ rcvr perform: selector with: self asNumber!

Item was changed:
  ----- Method: String>>adaptToString:andSend: (in category 'converting') -----
  adaptToString: rcvr andSend: selector
  	"If I am involved in arithmetic with a string, convert us both to
  	numbers, and return the printString of the result."
  
  	^ (rcvr asNumber perform: selector with: self asNumber) printString!

Item was changed:
  ----- Method: String>>asHtml (in category 'converting') -----
  asHtml
  	"Do the basic character conversion for HTML.  Leave all original return 
  	and tabs in place, so can conver back by simply removing bracked 
  	things. 4/4/96 tk"
  	| temp |
  	temp := self copyReplaceAll: '&' with: '&amp;'.
  	HtmlEntities keysAndValuesDo:
  		[:entity :char |
  		char = $& ifFalse:
  			[temp := temp copyReplaceAll: char asString with: '&' , entity , ';']].
  	temp := temp copyReplaceAll: '	' with: '	<IMG SRC="tab.gif" ALT="    ">'.
  	temp := temp copyReplaceAll: '
  ' with: '
  <BR>'.
  	^ temp
  
  "
  	'A<&>B' asHtml
  "!

Item was changed:
  ----- Method: String>>asLowercase (in category 'converting') -----
  asLowercase
  	"Answer a String made up from the receiver whose characters are all 
  	lowercase."
  
  	^ self copy asString translateToLowercase!

Item was changed:
  ----- Method: String>>asString (in category 'converting') -----
  asString
  	"Answer this string."
  
  	^ self
  !

Item was changed:
  ----- Method: String>>asUppercase (in category 'converting') -----
  asUppercase
  	"Answer a String made up from the receiver whose characters are all 
  	uppercase."
  
  	^self copy asString translateToUppercase!

Item was changed:
  ----- Method: String>>askIfAddStyle:req: (in category 'converting') -----
  askIfAddStyle: priorMethod req: requestor
  	^ self   "we are a string with no text style"!

Item was changed:
  ----- Method: String>>capitalized (in category 'converting') -----
  capitalized
  	"Return a copy with the first letter capitalized"
  	| cap |
  	self isEmpty ifTrue: [ ^self copy ].
  	cap := self copy.
  	cap at: 1 put: (cap at: 1) asUppercase.
  	^ cap!

Item was changed:
  ----- Method: String>>contractTo: (in category 'converting') -----
  contractTo: smallSize
  	"return myself or a copy shortened by ellipsis to smallSize"
  	| leftSize |
  	self size <= smallSize
  		ifTrue: [^ self].  "short enough"
  	smallSize < 5
  		ifTrue: [^ self copyFrom: 1 to: smallSize].    "First N characters"
  	leftSize := smallSize-2//2.
  	^ self copyReplaceFrom: leftSize+1		"First N/2 ... last N/2"
  		to: self size - (smallSize - leftSize - 3)
  		with: '...'
  "
  	'A clear but rather long-winded summary' contractTo: 18
  "!

Item was changed:
  ----- Method: String>>correctAgainst:continuedFrom: (in category 'converting') -----
  correctAgainst: wordList continuedFrom: oldCollection
  	"Like correctAgainst:.  Use when you want to correct against several lists, give nil as the first oldCollection, and nil as the last wordList."
  
  	^ wordList isNil
  		ifTrue: [ self correctAgainstEnumerator: nil
  					continuedFrom: oldCollection ]
  		ifFalse: [ self correctAgainstEnumerator: [ :action | wordList do: action without: nil]
  					continuedFrom: oldCollection ]!

Item was changed:
  ----- Method: String>>displayAt: (in category 'displaying') -----
  displayAt: aPoint 
  	"Display the receiver as a DisplayText at aPoint on the display screen."
  
  	self displayOn: Display at: aPoint!

Item was changed:
  ----- Method: String>>endsWithAnyOf: (in category 'testing') -----
  endsWithAnyOf: aCollection
  	aCollection do:[:suffix|
  		(self endsWith: suffix) ifTrue:[^true].
  	].
  	^false!

Item was changed:
  ----- Method: String>>findBetweenSubStrs: (in category 'accessing') -----
  findBetweenSubStrs: delimiters
  	"Answer the collection of String tokens that result from parsing self.  Tokens are separated by 'delimiters', which can be a collection of Strings, or a collection of Characters.  Several delimiters in a row are considered as just one separation."
  
  	| tokens keyStart keyStop |
  	tokens := OrderedCollection new.
  	keyStop := 1.
  	[keyStop <= self size] whileTrue:
  		[keyStart := self skipAnySubStr: delimiters startingAt: keyStop.
  		keyStop := self findAnySubStr: delimiters startingAt: keyStart.
  		keyStart < keyStop
  			ifTrue: [tokens add: (self copyFrom: keyStart to: (keyStop - 1))]].
  	^tokens!

Item was changed:
  ----- Method: String>>findString: (in category 'accessing') -----
  findString: subString
  	"Answer the index of subString within the receiver, starting at start. If 
  	the receiver does not contain subString, answer 0."
  	^self findString: subString startingAt: 1.!

Item was changed:
  ----- Method: String>>findTokens:includes: (in category 'accessing') -----
  findTokens: delimiters includes: subString
  	"Divide self into pieces using delimiters.  Return the piece that includes subString anywhere in it.  Is case sensitive (say asLowercase to everything beforehand to make insensitive)."
  
  ^ (self findTokens: delimiters) 
  	detect: [:str | (str includesSubString: subString)] 
  	ifNone: [nil]!

Item was changed:
  ----- Method: String>>findTokens:keep: (in category 'accessing') -----
  findTokens: delimiters keep: keepers
  	"Answer the collection of tokens that result from parsing self.  The tokens are seperated by delimiters, any of a string of characters.  If a delimiter is also in keepers, make a token for it.  (Very useful for carriage return.  A sole return ends a line, but is also saved as a token so you can see where the line breaks were.)"
  
  	| tokens keyStart keyStop |
  	tokens := OrderedCollection new.
  	keyStop := 1.
  	[keyStop <= self size] whileTrue:
  		[keyStart := self skipDelimiters: delimiters startingAt: keyStop.
  		keyStop to: keyStart-1 do: [:ii | 
  			(keepers includes: (self at: ii)) ifTrue: [
  				tokens add: (self copyFrom: ii to: ii)]].	"Make this keeper be a token"
  		keyStop := self findDelimiters: delimiters startingAt: keyStart.
  		keyStart < keyStop
  			ifTrue: [tokens add: (self copyFrom: keyStart to: (keyStop - 1))]].
  	^tokens!

Item was changed:
  ----- Method: String>>includesSubString: (in category 'testing') -----
  includesSubString: subString
  	^ (self findString: subString startingAt: 1) > 0!

Item was changed:
  ----- Method: String>>includesSubstring:caseSensitive: (in category 'testing') -----
  includesSubstring: aString caseSensitive: caseSensitive
  	
  	^ (self findString: aString startingAt: 1 caseSensitive: caseSensitive) > 0!

Item was changed:
  ----- Method: String>>isAllDigits (in category 'testing') -----
  isAllDigits
  	"whether the receiver is composed entirely of digits"
  	self do: [:c | c isDigit ifFalse: [^ false]].
  	^ true!

Item was changed:
  ----- Method: String>>isAllSeparators (in category 'testing') -----
  isAllSeparators
  	"whether the receiver is composed entirely of separators"
  	self do: [ :c | c isSeparator ifFalse: [ ^false ] ].
  	^true!

Item was changed:
  ----- Method: String>>isString (in category 'testing') -----
  isString
  	^ true!

Item was changed:
  ----- Method: String>>lastSpacePosition (in category 'accessing') -----
  lastSpacePosition
  	"Answer the character position of the final space or other separator character in the receiver, and 0 if none"
  	self size to: 1 by: -1 do:
  		[:i | ((self at: i) isSeparator) ifTrue: [^ i]].
  	^ 0
  
  "
  'fred the bear' lastSpacePosition
  'ziggie' lastSpacePosition
  'elvis ' lastSpacePosition
  'wimpy  ' lastSpacePosition
  '' lastSpacePosition
  "!

Item was changed:
  ----- Method: String>>numericSuffix (in category 'converting') -----
  numericSuffix
  	^ self stemAndNumericSuffix last
  
  "
  'abc98' numericSuffix
  '98abc' numericSuffix
  "!

Item was changed:
  ----- Method: String>>padded:to:with: (in category 'copying') -----
  padded: leftOrRight to: length with: char
  	leftOrRight = #left ifTrue:
  		[^ (String new: (length - self size max: 0) withAll: char) , self].
  	leftOrRight = #right ifTrue:
  		[^ self , (String new: (length - self size max: 0) withAll: char)].!

Item was changed:
  ----- Method: String>>romanNumber (in category 'converting') -----
  romanNumber
  	| value v1 v2 |
  	value := v1 := v2 := 0.
  	self reverseDo:
  		[:each |
  		v1 := #(1 5 10 50 100 500 1000) at: ('IVXLCDM' indexOf: each).
  		v1 >= v2
  			ifTrue: [value := value + v1]
  			ifFalse: [value := value - v1].
  		v2 := v1].
  	^ value!

Item was changed:
  ----- Method: String>>startsWithDigit (in category 'testing') -----
  startsWithDigit
  	"Answer whether the receiver's first character represents a digit"
  
  	^ self size > 0 and: [self first isDigit]!

Item was changed:
  ----- Method: String>>surroundedBySingleQuotes (in category 'converting') -----
  surroundedBySingleQuotes
  	"Answer the receiver with leading and trailing quotes.  "
  
  	^ $' asString, self, $' asString!

Item was changed:
  ----- Method: String>>translateToLowercase (in category 'converting') -----
  translateToLowercase
  	"Translate all characters to lowercase, in place"
  
  	self translateWith: LowercasingTable!

Item was changed:
  ----- Method: String>>truncateWithElipsisTo: (in category 'converting') -----
  truncateWithElipsisTo: maxLength
  	"Return myself or a copy suitably shortened but with elipsis added"
  
  	^ self size <= maxLength
  		ifTrue:
  			[self]
  		ifFalse:
  			[(self copyFrom: 1 to: (maxLength - 3)), '...']
  
  
  	"'truncateWithElipsisTo:' truncateWithElipsisTo: 20"!

Item was changed:
  ----- Method: String>>withoutTrailingBlanks (in category 'converting') -----
  withoutTrailingBlanks
  	"Return a copy of the receiver from which trailing blanks have been trimmed."
  
  	| last |
  	last := self findLast: [:c | c isSeparator not].
  	last = 0 ifTrue: [^ ''].  "no non-separator character"
  	^ self copyFrom: 1 to: last
  
  	" ' abc  d   ' withoutTrailingBlanks"
  !

Item was changed:
  ----- Method: TranscriptStream>>flush (in category 'stream extensions') -----
  flush
  	self endEntry
  !

Item was changed:
  ----- Method: WriteStream>>nextPut: (in category 'accessing') -----
  nextPut: anObject 
  	"Primitive. Insert the argument at the next position in the Stream
  	represented by the receiver. Fail if the collection of this stream is not an
  	Array or a String. Fail if the stream is positioned at its end, or if the
  	position is out of bounds in the collection. Fail if the argument is not
  	of the right type for the collection. Optional. See Object documentation
  	whatIsAPrimitive."
  
  	<primitive: 66>
  	position >= writeLimit
  		ifTrue: [^ self pastEndPut: anObject]
  		ifFalse: 
  			[position := position + 1.
  			^collection at: position put: anObject]!



More information about the Squeak-dev mailing list