[Pkg] The Trunk: Collections-ul.424.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Feb 12 00:31:20 UTC 2011


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

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

Name: Collections-ul.424
Author: ul
Time: 10 February 2011, 11:33:26.53 pm
UUID: f9d0075a-9597-ff42-9db7-cfd00ee6a60b
Ancestors: Collections-ul.423

- reimplemented String >> #expandMacrosWithArguments:

=============== Diff against Collections-ul.423 ===============

Item was changed:
  ArrayedCollection subclass: #String
  	instanceVariableNames: ''
+ 	classVariableNames: 'AsciiOrder CSLineEnders CSMacroCharacters CSNonSeparators CSSeparators CaseInsensitiveOrder CaseSensitiveOrder CrLfExchangeTable HtmlEntities LowercasingTable Tokenish UppercasingTable'
- 	classVariableNames: 'AsciiOrder CSLineEnders CSNonSeparators CSSeparators CaseInsensitiveOrder CaseSensitiveOrder CrLfExchangeTable HtmlEntities LowercasingTable Tokenish UppercasingTable'
  	poolDictionaries: ''
  	category: 'Collections-Strings'!
  
  !String commentStamp: '<historical>' prior: 0!
  A String is an indexed collection of Characters. Class String provides the abstract super class for ByteString (that represents an array of 8-bit Characters) and WideString (that represents an array of  32-bit characters).  In the similar manner of LargeInteger and SmallInteger, those subclasses are chosen accordingly for a string; namely as long as the system can figure out so, the String is used to represent the given string.
  
  Strings support a vast array of useful methods, which can best be learned by browsing and trying out examples as you find them in the code.
  
  Here are a few useful methods to look at...
  	String match:
  	String contractTo:
  
  String also inherits many useful methods from its hierarchy, such as
  	SequenceableCollection ,
  	SequenceableCollection copyReplaceAll:with:
  !

Item was changed:
  ----- Method: String class>>initialize (in category 'initialization') -----
  initialize   "self initialize"
  
  	| order |
  	AsciiOrder := (0 to: 255) as: ByteArray.
  
  	CaseInsensitiveOrder := AsciiOrder copy.
  	($a to: $z) do:
  		[:c | CaseInsensitiveOrder at: c asciiValue + 1
  				put: (CaseInsensitiveOrder at: c asUppercase asciiValue +1)].
  
  	"Case-sensitive compare sorts space, digits, letters, all the rest..."
  	CaseSensitiveOrder := ByteArray new: 256 withAll: 255.
  	order := -1.
  	' 0123456789' do:  "0..10"
  		[:c | CaseSensitiveOrder at: c asciiValue + 1 put: (order := order+1)].
  	($a to: $z) do:     "11-64"
  		[:c | CaseSensitiveOrder at: c asUppercase asciiValue + 1 put: (order := order+1).
  		CaseSensitiveOrder at: c asciiValue + 1 put: (order := order+1)].
  	1 to: CaseSensitiveOrder size do:
  		[:i | (CaseSensitiveOrder at: i) = 255 ifTrue:
  			[CaseSensitiveOrder at: i put: (order := order+1)]].
  	order = 255 ifFalse: [self error: 'order problem'].
  
  	"a table for translating to lower case"
  	LowercasingTable := String withAll: (Character allByteCharacters collect: [:c | c asLowercase]).
  
  	"a table for translating to upper case"
  	UppercasingTable := String withAll: (Character allByteCharacters collect: [:c | c asUppercase]).
  
  	"a table for testing tokenish (for fast numArgs)"
  	Tokenish := String withAll: (Character allByteCharacters collect:
  									[:c | c tokenish ifTrue: [c] ifFalse: [$~]]).
  
  	"CR and LF--characters that terminate a line"
  	CSLineEnders := CharacterSet crlf.
  
   	"separators and non-separators"
  	CSSeparators := CharacterSet separators.
  	CSNonSeparators := CSSeparators complement.
  	
+ 	"% and < for #expandMacros*"
+ 	CSMacroCharacters := CharacterSet newFrom: '%<'.
+ 	
  	"a table for exchanging cr with lf and vica versa"
  	CrLfExchangeTable := Character allByteCharacters collect: [ :each |
  		each
  			caseOf: {
  				[ Character cr ] -> [ Character lf ].
  				[ Character lf ] -> [ Character cr ] }
  			otherwise: [ each ] ]!

Item was changed:
  ----- Method: String>>expandMacrosWithArguments: (in category 'formatting') -----
  expandMacrosWithArguments: anArray 
+ 	
+ 	^self class new: self size streamContents: [ :output |
+ 		| lastIndex nextIndex characterSet |
+ 		lastIndex := 1.
+ 		[ (nextIndex := self indexOfAnyOf: CSMacroCharacters startingAt: lastIndex) = 0 ] whileFalse: [
+ 			nextIndex = lastIndex ifFalse: [
+ 				output next: nextIndex - lastIndex putAll: self startingAt: lastIndex ].
+ 			(self at: nextIndex) == $% 
+ 				ifTrue: [ output nextPut: (self at: (nextIndex := nextIndex + 1)) ]
+ 				ifFalse: [ 
+ 					| nextCharacter argumentIndex |
+ 					nextCharacter := (self at: (nextIndex := nextIndex + 1)) asUppercase.
+ 					nextCharacter == $N ifTrue: [ output cr ].
+ 					nextCharacter == $T ifTrue: [ output tab ].
+ 					(nextCharacter between: $0 and: $9) ifTrue: [
+ 						argumentIndex := nextCharacter digitValue.
+ 						[ (nextIndex := nextIndex + 1) <= self size and: [
+ 							(nextCharacter := self at: nextIndex) between: $0 and: $9 ] ] whileTrue: [
+ 								argumentIndex := argumentIndex * 10 + nextCharacter digitValue ].
+ 						nextCharacter := nextCharacter asUppercase ].
+ 					nextCharacter == $P ifTrue: [ output print: (anArray at: argumentIndex) ].
+ 					nextCharacter == $S ifTrue: [ output nextPutAll: (anArray at: argumentIndex) ].
+ 					nextCharacter == $? ifTrue: [ 
+ 						| trueEnd falseEnd |
+ 						trueEnd := self indexOf: $: startingAt: nextIndex + 1.
+ 						falseEnd := self indexOf: $> startingAt: trueEnd + 1.
+ 						(anArray at: argumentIndex)
+ 							ifTrue: [ output next: trueEnd - nextIndex - 1 putAll: self startingAt: nextIndex + 1 ]
+ 							ifFalse: [ output next: falseEnd - trueEnd - 1 putAll: self startingAt: trueEnd + 1 ].
+ 						nextIndex := falseEnd - 1 ].
+ 					(self at: (nextIndex := nextIndex + 1)) == $> ifFalse: [
+ 						self error: '> expected' ] ].
+ 			lastIndex := nextIndex + 1 ].
+ 		lastIndex <= self size ifTrue: [
+ 			output next: self size - lastIndex + 1 putAll: self startingAt: lastIndex ] ]!
- 	| newStream readStream char index |
- 	newStream := WriteStream on: (String new: self size).
- 	readStream := ReadStream on: self.
- 	[readStream atEnd] whileFalse: 
- 			[char := readStream next.
- 			char == $< 
- 				ifTrue: 
- 					[| nextChar |
- 					nextChar := readStream next asUppercase.
- 					nextChar == $N ifTrue: [newStream cr].
- 					nextChar == $T ifTrue: [newStream tab].
- 					nextChar isDigit 
- 						ifTrue: 
- 							[index := nextChar digitValue.
- 							
- 							[readStream atEnd 
- 								or: [(nextChar := readStream next asUppercase) isDigit not]] 
- 									whileFalse: [index := index * 10 + nextChar digitValue]].
- 					nextChar == $? 
- 						ifTrue: 
- 							[| trueString falseString |
- 							trueString := readStream upTo: $:.
- 							falseString := readStream upTo: $>.
- 							readStream position: readStream position - 1.
- 							newStream 
- 								nextPutAll: ((anArray at: index) ifTrue: [trueString] ifFalse: [falseString])].
- 					nextChar == $P 
- 						ifTrue: [newStream nextPutAll: (anArray at: index) printString].
- 					nextChar == $S ifTrue: [newStream nextPutAll: (anArray at: index)].
- 					readStream skipTo: $>]
- 				ifFalse: 
- 					[newStream nextPut: (char == $% ifTrue: [readStream next] ifFalse: [char])]].
- 	^newStream contents!



More information about the Packages mailing list