[Pkg] The Trunk: Collections-nice.193.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Nov 16 16:50:25 UTC 2009


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

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

Name: Collections-nice.193
Author: nice
Time: 16 November 2009, 5:50:18 am
UUID: a94e2d4b-aa4b-c94c-b082-05ad77bef91c
Ancestors: Collections-nice.192

Handle more crlf cases

=============== Diff against Collections-nice.192 ===============

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: (collection species 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 changed:
  ----- Method: String>>withInternetLineEndings (in category 'internet') -----
  withInternetLineEndings
+ 	"change line endings from CR's to CRLF's.  This is probably in prepration for sending a string over the Internet"
+ 	^self class
+ 		new: self size * 16 // 15 "provisions for CR-LF pairs"
+ 		streamContents: [ :stream |
+ 			self lineIndicesDo: [:start :endWithoutDelimiters :end |
+ 				stream nextPutAll: (self copyFrom: start to: endWithoutDelimiters).
+ 				endWithoutDelimiters = end ifFalse: [	stream cr; lf] ] ]!
- 	"change line endings from CR's to CRLF's.  This is probably in
- prepration for sending a string over the Internet"
- 	| cr lf |
- 	cr := Character cr.
- 	lf := Character linefeed.
- 	^self class streamContents: [ :stream |
- 		self do: [ :c |
- 			stream nextPut: c.
- 			c = cr ifTrue:[ stream nextPut: lf ]. ] ].!

Item was changed:
  ----- Method: String>>withSqueakLineEndings (in category 'internet') -----
  withSqueakLineEndings
  	"assume the string is textual, and that CR, LF, and CRLF are all 
  	valid line endings.  Replace each occurence with a single CR"
+ 	| cr lf crlf inPos outPos outString lineEndPos newOutPos |
- 	| cr lf input c crlf inPos outPos outString lineEndPos newOutPos |
  	cr := Character cr.
  	lf := Character linefeed.
+ 	crlf := CharacterSet crlf.
- 	crlf := CharacterSet new.
- 	crlf add: cr; add: lf.
  
  	inPos := 1.
  	outPos := 1.
+ 	outString := String new: self size.
- 	outString :=
-  String new: self size.
  
  	[ lineEndPos := self indexOfAnyOf: crlf startingAt: inPos ifAbsent: [0].
  		lineEndPos ~= 0 ] whileTrue: [
  			newOutPos := outPos + (lineEndPos - inPos + 1).
  			outString replaceFrom: outPos to: newOutPos - 2 with: self startingAt: inPos.
  			outString at: newOutPos-1 put: cr.
  			outPos := newOutPos.
  
  			((self at: lineEndPos) = cr and: [ lineEndPos < self size and: [ (self at: lineEndPos+1) = lf ] ]) ifTrue: [
  				"CRLF ending"
  				inPos := lineEndPos + 2 ]
  			ifFalse: [ 
  				"CR or LF ending"
  				inPos := lineEndPos + 1 ]. ].
  
  	"no more line endings.  copy the rest"
  	newOutPos := outPos + (self size - inPos + 1).
  	outString replaceFrom: outPos to: newOutPos-1 with: self startingAt: inPos.
  
  	^outString copyFrom: 1 to: newOutPos-1
  	!

Item was changed:
  ----- Method: String>>withBlanksTrimmed (in category 'converting') -----
  withBlanksTrimmed
  	"Return a copy of the receiver from which leading and trailing blanks have been trimmed."
  
  	| first last |
+ 	first := self indexOfAnyOf: CSNonSeparators startingAt: 1 ifAbsent: [0].
- 	first := self findFirst: [ :c | c isSeparator not ].
  	first = 0 ifTrue: [ ^'' ].  "no non-separator character"
+ 	last := self lastIndexOfAnyOf: CSNonSeparators startingAt: self size ifAbsent: [self size].
- 	last := self findLast: [ :c | c isSeparator not ].
  	(first = 1 and: [ last = self size ]) ifTrue: [ ^self copy ].
  	^self
  		copyFrom: first
  		to: last
  !



More information about the Packages mailing list