terminals/Xtreams__FileWriteStream.st
changeset 9 6c90659cf105
child 25 02e7c3b6f63c
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/terminals/Xtreams__FileWriteStream.st	Mon Aug 22 16:04:00 2011 +0000
@@ -0,0 +1,147 @@
+"{ Package: 'stx:goodies/xtreams/terminals' }"
+
+"{ NameSpace: Xtreams }"
+
+WriteStream subclass:#FileWriteStream
+	instanceVariableNames:'position isPositionable contentsSpecies'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'My Classes'
+!
+
+FileWriteStream comment:'Writes to a file. File write streams can be created via the usual #writing message or via #appending which opens the file in appending mode. In appending mode, you cannot position the stream before the end of the file contents, so you can never overwrite existing contents. In writing mode, the file will be truncated at stream''s current position when #close is called. To keep the entire contents of the file, use -= 0 to skip to the end before closing. This behavior is different from the classic streams which would erase the contents of the file on opening. The stream is binary and naturally positionable.
+{{{
+	| file |
+	file := ''/dev/shm/xtreams-test'' asFilename.
+	[	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'' 
+		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
+
+'
+!
+
+
+!FileWriteStream methodsFor:'accessing'!
+
+insert: anInteger from: aSequenceableCollection at: startIndex
+	^self shouldNotImplement.
+
+	"While it might seem desireable to be able to insert in to a file, the reality is you can only do so if you can read and write to the file. if you can read and write to the file, the fileSize becomes indeterminate. The only reasonable way to insert in to a file is to memory map it and access it with a PointerWriteStream instead."
+!
+
+write: anInteger from: aSequenceableCollection at: startIndex
+	| count wrote |
+	anInteger isZero ifTrue: [^0].
+	count := 0.
+	[count < anInteger] whileTrue:
+		[wrote := destination writeFrom: aSequenceableCollection startingAt: startIndex + count for: anInteger.
+		wrote isZero ifTrue: [(Incomplete on: aSequenceableCollection count: count at: startIndex) raise].
+		count := count + wrote.
+		position := position + wrote].
+	^anInteger
+! !
+
+!FileWriteStream methodsFor:'initialize-release'!
+
+close
+	destination isActive ifFalse: [^self].
+	destination truncateTo: position.
+	destination close
+!
+
+contentsSpecies
+	^contentsSpecies
+!
+
+contentsSpecies: aClass
+	contentsSpecies := aClass
+!
+
+flush
+	destination isActive ifFalse: [^self].
+	destination commit
+!
+
+isPositionable: aBoolean
+	"Only set to false when the file is open in append mode."
+
+	isPositionable := aBoolean
+!
+
+on: anAccessor
+	super on: anAccessor.
+	contentsSpecies := ByteArray.
+	isPositionable := true.
+	position := 0
+! !
+
+!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.
+	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.
+	anInteger = count ifTrue: [^anInteger].
+	(Incomplete count: count) raise
+!
+
+length
+	self isPositionable ifFalse: [self error: 'This stream is not positionable.'].
+	^destination fileSize
+!
+
+position
+	self isPositionable ifFalse: [self error: 'This stream is not positionable.'].
+	^position
+!
+
+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.
+	position := available.
+	available = aPosition ifTrue: [ ^aPosition ].
+	(Incomplete count: available) raise
+! !
+
+!FileWriteStream methodsFor:'testing'!
+
+isPositionable
+	^isPositionable
+! !
+
+!FileWriteStream class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id$'
+! !