[squeak-dev] The Trunk: Files-topa.146.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Oct 8 19:10:10 UTC 2015


Tobias Pape uploaded a new version of Files to project The Trunk:
http://source.squeak.org/trunk/Files-topa.146.mcz

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

Name: Files-topa.146
Author: topa
Time: 8 October 2015, 9:10:00.604 pm
UUID: c0933530-a77b-4266-9c56-3d984ede0bad
Ancestors: Files-mt.145

Deprecate CrLfFileStream (see CrLfFileStream class>>#new)

=============== Diff against Files-mt.145 ===============

Item was removed:
- StandardFileStream subclass: #CrLfFileStream
- 	instanceVariableNames: 'lineEndConvention'
- 	classVariableNames: 'Cr CrLf Lf LineEndDefault LineEndStrings LookAheadCount'
- 	poolDictionaries: ''
- 	category: 'Files-Kernel'!
- 
- !CrLfFileStream commentStamp: 'ul 12/26/2010 03:13' prior: 0!
- This class is now obsolete, use MultiByteFileStream instead.
- 
- I am the same as a regular file stream, except that when I am in text mode, I will automatically convert line endings between the underlying platform's convention, and Squeak's convention of carriage-return only.  The goal is that Squeak text files can be treated as OS text files, and vice versa.
- 
- In binary mode, I behave identically to a StandardFileStream.
- 
- To enable CrLfFileStream as the default file stream class for an entire image, modify FileStream class concreteStream .
- 
- 
- There are two caveats on programming with CrLfFileStream.
- 
- First, the choice of text mode versus binary mode affects which characters are visible in Squeak, and no longer just affects whether those characters are returned as Character's or as Integer's.  Thus the choice of mode needs to be made very carefully, and must be based on intent instead of convenience of representation.  The methods asString, asByteArray, asCharacter, and asInteger can be used to convert between character and integer representations.  (Arguably, file streams should accept either strings or characters in nextPut: and nextPutAll:, but that is not the case right now.)
- 
- Second, arithmetic on positions no longer works, because one character that Squeak sees (carriage return) could map to two characters in the underlying file (carriage return plus line feed, on MS Windows and MS DOS).  Comparison between positions still works.  (This caveat could perhaps be fixed by maintaining a map between Squeak positions and positions in the underlying file, but it is complicated.  Consider, for example, updates to the middle of the file.  Also, consider that text files are rarely updated in the middle of the file, and that general random access to a text file is rarely very useful.  If general random access with specific file counts is desired, then the file is starting to sound like a binary file instead of a text file.)
- 
- !

Item was removed:
- ----- Method: CrLfFileStream class>>defaultToCR (in category 'class initialization') -----
- defaultToCR
- 	"CrLfFileStream defaultToCR"
- 	LineEndDefault := #cr.!

Item was removed:
- ----- Method: CrLfFileStream class>>defaultToCRLF (in category 'class initialization') -----
- defaultToCRLF
- 	"CrLfFileStream defaultToCRLF"
- 	LineEndDefault := #crlf.!

Item was removed:
- ----- Method: CrLfFileStream class>>defaultToLF (in category 'class initialization') -----
- defaultToLF
- 	"CrLfFileStream defaultToLF"
- 	LineEndDefault := #lf.!

Item was removed:
- ----- Method: CrLfFileStream class>>guessDefaultLineEndConvention (in category 'class initialization') -----
- guessDefaultLineEndConvention
- 	"Lets try to guess the line end convention from what we know about the
- 	path name delimiter from FileDirectory."
- 	FileDirectory pathNameDelimiter = $:
- 		ifTrue: [^ self defaultToCR].
- 	FileDirectory pathNameDelimiter = $/
- 		ifTrue: [((Smalltalk osVersion) beginsWith: 'darwin')
- 				ifTrue: [^ self defaultToCR]
- 				ifFalse: [^ self defaultToLF]].
- 	FileDirectory pathNameDelimiter = $\
- 		ifTrue: [^ self defaultToCRLF].
- 	"in case we don't know"
- 	^ self defaultToCR!

Item was removed:
- ----- Method: CrLfFileStream class>>initialize (in category 'class initialization') -----
- initialize
- 	"CrLfFileStream initialize"
- 	Cr := Character cr.
- 	Lf := Character lf.
- 	CrLf := String with: Cr with: Lf.
- 	LineEndStrings := Dictionary new.
- 	LineEndStrings at: #cr put: (String with: Character cr).
- 	LineEndStrings at: #lf put: (String with: Character lf).
- 	LineEndStrings at: #crlf put: (String with: Character cr with: Character lf).
- 	LookAheadCount := 2048.
- 	Smalltalk addToStartUpList: self.
- 	self startUp.!

Item was removed:
- ----- Method: CrLfFileStream class>>new (in category 'class initialization') -----
- new
- 
- 	self deprecated: 'This class is now obsolete, use MultiByteFileStream instead.'.
- 	^ (MultiByteFileStream new ascii) wantsLineEndConversion: true; yourself.
- 
- !

Item was removed:
- ----- Method: CrLfFileStream class>>startUp (in category 'class initialization') -----
- startUp
- 	self guessDefaultLineEndConvention!

Item was removed:
- ----- Method: CrLfFileStream>>ascii (in category 'access') -----
- ascii
- 	super ascii.
- 	self detectLineEndConvention!

Item was removed:
- ----- Method: CrLfFileStream>>binary (in category 'access') -----
- binary
- 	super binary.
- 	lineEndConvention := nil!

Item was removed:
- ----- Method: CrLfFileStream>>convertStringFromCr: (in category 'private') -----
- convertStringFromCr: aString 
- 	| inStream outStream |
- 	lineEndConvention ifNil: [^ aString].
- 	lineEndConvention == #cr ifTrue: [^ aString].
- 	lineEndConvention == #lf ifTrue: [^ aString copy replaceAll: Cr with: Lf].
- 	"lineEndConvention == #crlf"
- 	inStream := ReadStream on: aString.
- 	outStream := WriteStream on: (String new: aString size).
- 	[inStream atEnd]
- 		whileFalse: 
- 			[outStream nextPutAll: (inStream upTo: Cr).
- 			(inStream atEnd not or: [aString last = Cr])
- 				ifTrue: [outStream nextPutAll: CrLf]].
- 	^ outStream contents!

Item was removed:
- ----- Method: CrLfFileStream>>convertStringToCr: (in category 'private') -----
- convertStringToCr: aString 
- 	| inStream outStream |
- 	lineEndConvention ifNil: [^ aString].
- 	lineEndConvention == #cr ifTrue: [^ aString].
- 	lineEndConvention == #lf ifTrue: [^ aString copy replaceAll: Lf with: Cr].
- 	"lineEndConvention == #crlf"
- 	inStream := ReadStream on: aString.
- 	outStream := WriteStream on: (String new: aString size).
- 	[inStream atEnd]
- 		whileFalse: 
- 			[outStream nextPutAll: (inStream upTo: Cr).
- 			(inStream atEnd not or: [aString last = Cr])
- 				ifTrue: 
- 					[outStream nextPut: Cr.
- 					inStream peek = Lf ifTrue: [inStream next]]].
- 	^ outStream contents!

Item was removed:
- ----- Method: CrLfFileStream>>detectLineEndConvention (in category 'access') -----
- detectLineEndConvention
- 	"Detect the line end convention used in this stream. The result may be either #cr, #lf or #crlf."
- 	| char numRead pos |
- 	self isBinary ifTrue: [^ self error: 'Line end conventions are not used on binary streams'].
- 	lineEndConvention := LineEndDefault.
- 	"Default if nothing else found"
- 	numRead := 0.
- 	pos := super position.
- 	[super atEnd not and: [numRead < LookAheadCount]]
- 		whileTrue: 
- 			[char := super next.
- 			char = Lf
- 				ifTrue: 
- 					[super position: pos.
- 					^ lineEndConvention := #lf].
- 			char = Cr
- 				ifTrue: 
- 					[super peek = Lf
- 						ifTrue: [lineEndConvention := #crlf]
- 						ifFalse: [lineEndConvention := #cr].
- 					super position: pos.
- 					^ lineEndConvention].
- 			numRead := numRead + 1].
- 	super position: pos.
- 	^ lineEndConvention!

Item was removed:
- ----- Method: CrLfFileStream>>lineEndConvention (in category 'access') -----
- lineEndConvention
- 
- 	^lineEndConvention!

Item was removed:
- ----- Method: CrLfFileStream>>next (in category 'access') -----
- next
-     | char secondChar |
-     char := super next.
-     self isBinary ifTrue: [^char].
-     char == Cr ifTrue:
-         [secondChar := super next.
-         secondChar ifNotNil: [secondChar == Lf ifFalse: [self skip: -1]].
-         ^Cr].
-     char == Lf ifTrue: [^Cr].
-     ^char!

Item was removed:
- ----- Method: CrLfFileStream>>next: (in category 'access') -----
- next: n
- 
- 		| string peekChar |
- 		string := super next: n.
- 		string size = 0 ifTrue: [ ^string ].
- 		self isBinary ifTrue: [ ^string ].
- 
- 		"if we just read a CR, and the next character is an LF, then skip the LF"
- 		( string last = Character cr ) ifTrue: [
- 			peekChar := super next.		"super peek doesn't work because it relies on #next"
- 			peekChar ~= Character lf ifTrue: [
- 				super position: (super position - 1) ]. ].
-  
- 		string := string withSqueakLineEndings.
- 
- 		string size = n ifTrue: [ ^string ].
- 
- 		"string shrunk due to embedded crlfs; make up the difference"
- 		^string, (self next: n - string size)!

Item was removed:
- ----- Method: CrLfFileStream>>nextPut: (in category 'access') -----
- nextPut: char 
- 	(lineEndConvention notNil and: [char = Cr])
- 		ifTrue: [super nextPutAll: (LineEndStrings at: lineEndConvention)]
- 		ifFalse: [super nextPut: char].
- 	^ char!

Item was removed:
- ----- Method: CrLfFileStream>>nextPutAll: (in category 'access') -----
- nextPutAll: aString 
- 	super nextPutAll: (self convertStringFromCr: aString).
- 	^ aString
- !

Item was removed:
- ----- Method: CrLfFileStream>>open:forWrite: (in category 'open/close') -----
- open: aFileName forWrite: writeMode 
- 	"Open the receiver.  If writeMode is true, allow write, else access will be 
- 	read-only. "
- 	| result |
- 	result := super open: aFileName forWrite: writeMode.
- 	result ifNotNil: [self detectLineEndConvention].
- 	^ result!

Item was removed:
- ----- Method: CrLfFileStream>>peek (in category 'access') -----
- peek
- 	"Answer what would be returned if the message next were sent to the receiver. If the receiver is at the end, answer nil.  "
- 	| next pos |
- 	self atEnd ifTrue: [^ nil].
- 	pos := self position.
- 	next := self next.
- 	self position: pos.
- 	^ next!

Item was removed:
- ----- Method: CrLfFileStream>>upTo: (in category 'access') -----
- upTo: aCharacter
- 	| newStream char |
- 	newStream := WriteStream on: (String new: 100).
- 	[(char := self next) isNil or: [char == aCharacter]]
- 		whileFalse: [newStream nextPut: char].
- 	^ newStream contents
- !

Item was removed:
- ----- Method: CrLfFileStream>>upToAnyOf:do: (in category 'access') -----
- upToAnyOf: delimiters do: aBlock
- 
- 	^String new: 1000 streamContents: [ :stream |
- 		| ch |
- 		[ (ch := self next) == nil or: [ (delimiters includes: ch) and: [aBlock value: ch. true] ] ] 
- 			whileFalse: [ stream nextPut: ch ] ]!

Item was removed:
- ----- Method: CrLfFileStream>>verbatim: (in category 'access') -----
- verbatim: aString 
- 	super verbatim: (self convertStringFromCr: aString).
- 	^ aString!



More information about the Squeak-dev mailing list