terminals/Xtreams__FileWriteStream.st
changeset 109 9587e2df7029
parent 78 a9dd8b69b39f
--- a/terminals/Xtreams__FileWriteStream.st	Thu Feb 16 18:11:55 2012 +0000
+++ b/terminals/Xtreams__FileWriteStream.st	Fri Mar 15 22:45:50 2013 +0000
@@ -3,7 +3,7 @@
 "{ NameSpace: Xtreams }"
 
 WriteStream subclass:#FileWriteStream
-	instanceVariableNames:'position isPositionable contentsSpecies'
+	instanceVariableNames:'position isPositionable contentsSpecies filename'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Xtreams-Terminals'
@@ -13,23 +13,23 @@
 {{{
 	| file |
 	file := ''/dev/shm/xtreams-test'' asFilename.
-	[	file writing write: ''Hello''; close.
+	[       file writing write: ''Hello''; close.
 		file appending write: '' World!!''; close.
 		file contentsOfEntireFile.
 	] ensure: [ file delete ]
 }}}
 It is also possible to send #reading or #writing to a pre-opened IOAcccessor if some other opening mode configuration is desirable. For example to emulate the classic write stream opening behavior, you can use the following:
 {{{
-	(IOAccessor openFileNamed: ''/dev/shm/xtreams-test'' 
+	(IOAccessor openFileNamed: ''/dev/shm/xtreams-test''
 		direction: IOAccessor writeOnly
 		creation: IOAccessor truncateOrCreate
 	) writing close
 }}}
 
 Instance Variables
-	position	<Integer> current position of the stream
-	isPositionable	<Boolean> indicates that the file is open in append mode
-	contentsSpecies	<Class> species for collections of elements of this stream
+	position        <Integer> current position of the stream
+	isPositionable  <Boolean> indicates that the file is open in append mode
+	contentsSpecies <Class> species for collections of elements of this stream
 
 '
 !
@@ -44,22 +44,22 @@
 !
 
 write: anInteger from: aSequenceableCollection at: startIndex
-        | count wrote |
-        anInteger isZero ifTrue: [^0].
-        count := 0.
-        [count < anInteger] whileTrue:
-                [wrote := destination writeBytes: anInteger from: aSequenceableCollection startingAt: startIndex + count.
-                wrote isZero ifTrue: [(Incomplete on: aSequenceableCollection count: count at: startIndex) raise].
-                count := count + wrote.
-                position := position + wrote].
-        ^anInteger
+	| count wrote |
+	anInteger isZero ifTrue: [^0].
+	count := 0.
+	[count < anInteger] whileTrue:
+		[wrote := destination writeBytes: anInteger from: aSequenceableCollection startingAt: startIndex + count.
+		wrote isZero ifTrue: [(Incomplete on: aSequenceableCollection count: count at: startIndex) raise].
+		count := count + wrote.
+		position := position + wrote].
+	^anInteger
 ! !
 
 !FileWriteStream methodsFor:'initialize-release'!
 
 close
-        destination isValid ifFalse: [^self].
-        destination close
+	destination isValid ifFalse: [^self].
+	destination close
 !
 
 contentsSpecies
@@ -86,33 +86,40 @@
 	position := 0
 ! !
 
+!FileWriteStream methodsFor:'private'!
+
+setFilename: fn
+
+    filename := fn
+! !
+
 !FileWriteStream methodsFor:'seeking'!
 
 ++ anInteger
-        | count |
-        self isPositionable ifFalse: [self error: 'This stream is not positionable.'].
-        anInteger < 0 ifTrue: [ ^self -- anInteger negated ].
-        count := self available min: anInteger.
-        position := position + count.
-        destination seekTo: position from: #begin.
-        count < anInteger ifTrue: [(Incomplete count: count) raise].
-        ^anInteger
+	| count |
+	self isPositionable ifFalse: [self error: 'This stream is not positionable.'].
+	anInteger < 0 ifTrue: [ ^self -- anInteger negated ].
+	count := self available min: anInteger.
+	position := position + count.
+	destination seekTo: position from: #begin.
+	count < anInteger ifTrue: [(Incomplete count: count) raise].
+	^anInteger
 !
 
 -- anInteger
-        | count |
-        self isPositionable ifFalse: [self error: 'This stream is not positionable.'].
-        anInteger < 0 ifTrue: [ ^self ++ anInteger negated ].
-        count := position min: anInteger.
-        position := position - count.
-        destination seekTo: position from: #begin.
-        anInteger = count ifTrue: [^anInteger].
-        (Incomplete count: count) raise
+	| count |
+	self isPositionable ifFalse: [self error: 'This stream is not positionable.'].
+	anInteger < 0 ifTrue: [ ^self ++ anInteger negated ].
+	count := position min: anInteger.
+	position := position - count.
+	destination seekTo: position from: #begin.
+	anInteger = count ifTrue: [^anInteger].
+	(Incomplete count: count) raise
 !
 
 length
 	self isPositionable ifFalse: [self error: 'This stream is not positionable.'].
-	^destination fileSize
+	^filename fileSize
 !
 
 position
@@ -121,14 +128,14 @@
 !
 
 position: aPosition
-        | available |
-        self isPositionable ifFalse: [self error: 'This stream is not positionable.'].
-        aPosition < 0 ifTrue: [ Incomplete zero raise ].
-        available := aPosition min: self length.
-        destination seekTo: available from: #begin.
-        position := available.
-        available = aPosition ifTrue: [ ^aPosition ].
-        (Incomplete count: available) raise
+	| available |
+	self isPositionable ifFalse: [self error: 'This stream is not positionable.'].
+	aPosition < 0 ifTrue: [ Incomplete zero raise ].
+	available := aPosition min: self length.
+	destination seekTo: available from: #begin.
+	position := available.
+	available = aPosition ifTrue: [ ^aPosition ].
+	(Incomplete count: available) raise
 ! !
 
 !FileWriteStream methodsFor:'testing'!
@@ -139,6 +146,8 @@
 
 !FileWriteStream class methodsFor:'documentation'!
 
-version_SVN
-    ^ '$Id$'
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
+