terminals/Xtreams__PointerWriteStream.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 01 Feb 2012 00:41:14 +0000
changeset 99 677c81c943e4
parent 96 85e395d8e3d7
permissions -rw-r--r--
build files regenerated

"{ Package: 'stx:goodies/xtreams/terminals' }"

"{ NameSpace: Xtreams }"

WriteStream subclass:#PointerWriteStream
	instanceVariableNames:'length position contentsSpecies'
	classVariableNames:''
	poolDictionaries:'Xtreams::XtreamsPool'
	category:'Xtreams-Terminals'
!

PointerWriteStream comment:'Write stream on external heap, commonly used to marshal input for an external library call. The terminal is a CPointer and its associated CType is used to interpret the bytes on the heap. The length of the stream must be set, to avoid writing past the allocated memory space. If more objects are written than can fit in the pre-allocated space, a new larger heap chunk is automatically allocated to accommodate it (the contents of the old chunk are copied over and the chunk is deallocated). Similarly closing the write stream will reallocate and shrink the write stream to its position at that time.
{{{
	| buffer |
	buffer := CIntegerType unsignedChar malloc: 50.
	[	buffer writing
			length: 50;
			write: ''Hello World!!''.
		buffer reading
			length: 12;
			contentsSpecies: ByteString;
			rest
	] ensure: [ buffer free ]
}}}

Instance Variables
	length	<Integer> allocated size of the stream as a number of elements of associated CType
	position	<Integer> current position of the stream
	contentsSpecies	<Class> species for collections of elements of this stream

'
!


!PointerWriteStream methodsFor:'accessing'!

contents
	| cache |
	cache := self contentsSpecies withSize: position.
	destination copyAt: 0 to: cache size: position startingAt: 1.
	^cache
!

insert: anInteger from: aSequenceableCollection at: startIndex
	| shift |
	shift := length - position.
	self resizeTo: length + anInteger.
	OSSystemSupport concreteClass new copyMemoryTo: destination + position + anInteger from: destination + position size: shift.
	self copyFrom: aSequenceableCollection size: anInteger startingAt: startIndex.
	position := position + anInteger.
	^anInteger
!

put: anObject
	| free |
	free := length - position.
	free < 1 ifTrue: [self resizeTo: length + 1].
	destination at: position put: anObject.
	position := position + 1
!

write: anInteger from: aSequenceableCollection at: startIndex
	| available |
	available := length - position.
	available < anInteger ifTrue: [self resizeTo: length + anInteger - available].
	self copyFrom: aSequenceableCollection size: anInteger startingAt: startIndex.
	position := position + anInteger.
	^anInteger
! !

!PointerWriteStream methodsFor:'initialize-release'!

close
	self resizeTo: position
!

contentsSpecies
	^contentsSpecies
!

contentsSpecies: aClass
	contentsSpecies := aClass
!

flush
!

length: anObject
	length := anObject
!

on: aPointer
	super on: aPointer.
	contentsSpecies := Array.
	length := 1.
	position := 0
! !

!PointerWriteStream methodsFor:'private'!

copyFrom: aSequenceableCollection size: anInteger startingAt: startIndex

	destination type = UnsignedChar
		ifTrue: [ 	destination copyAt: position from: aSequenceableCollection size: anInteger startingAt: startIndex. ]
		ifFalse: [
			0 to: anInteger - 1 do: [ :i |
				destination at: position + i put: (aSequenceableCollection at: startIndex + i) ] ]
!

resizeTo: anInteger
	| replacement beGC |
	length = anInteger ifTrue: [^self].
	replacement := destination type baseReferentType malloc: anInteger.
	OSSystemSupport concreteClass new copyMemoryTo: replacement from: destination size: (length min: anInteger).
	beGC := CPointer.GarbageCollectablePointers includes: destination.
	destination free.
	destination referentAddress: replacement referentAddress.
	beGC ifTrue: [destination beGarbageCollectable].
	length := anInteger
! !

!PointerWriteStream methodsFor:'seeking'!

++ anInteger
	| count |
	anInteger < 0 ifTrue: [ ^self -- anInteger negated ].
	count := self available min: anInteger.
	position := position + count.
	count < anInteger ifTrue: [(Incomplete count: count) raise].
	^anInteger
!

-- anInteger
	| count |
	anInteger < 0 ifTrue: [ ^self ++ anInteger negated ].
	count := position min: anInteger.
	position := position - count.
	count = anInteger ifTrue: [^anInteger].
	(Incomplete count: count) raise
!

length
	^length
!

position
	^position
!

position: aPosition
	" Return to a bookmarked position on this stream. "

	aPosition < 0 ifTrue: [Incomplete zero raise].
	aPosition > length ifFalse: [ ^position := aPosition ].
	position := length.
	^(Incomplete count: length) raise
! !

!PointerWriteStream methodsFor:'testing'!

isPositionable
	^true
! !

!PointerWriteStream class methodsFor:'documentation'!

version_SVN
    ^ '$Id$'
! !