terminals/Xtreams__PointerReadStream.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 01 Feb 2012 00:37:59 +0000
changeset 98 bd334e72464f
parent 96 85e395d8e3d7
child 100 bd080ca99f68
permissions -rw-r--r--
Fix in #read:into:at:

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

"{ NameSpace: Xtreams }"

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

PointerReadStream comment:'Read stream on external heap, commonly used to unmarshal output or 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 should be set, to avoid reading past the allocated memory space.
{{{
	| 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
	contentsSpecies	<Class> species for collections of elements of this stream
	position	<Integer> current position of the stream

'
!


!PointerReadStream methodsFor:'accessing'!

get
	| object |
	(length isNil or: [ position < length ]) ifFalse: [ Incomplete zero raise ].
	object := source at: position.
	position := position + 1.
	^object
!

read: anInteger into: aSequenceableCollection at: startIndex
        
        | count available |
        count := (available := self available) isNil ifTrue: [ anInteger ] ifFalse: [ available min: anInteger ].
        self breakPoint: #jv.
        self breakPoint: #mk.
        "There is no UnsignedChar here..."
        source type referentType = UnsignedChar
                ifTrue: [ source copyAt: position to: aSequenceableCollection size: anInteger startingAt: startIndex. ]
                ifFalse: [ startIndex to: startIndex + count - 1 do: [ :i | aSequenceableCollection at: i put: self get ] ].
        position := position + count.
        ^count < anInteger
                ifTrue: [ (Incomplete on: aSequenceableCollection count: count at: startIndex) raise ]
                ifFalse: [ count ]

    "Modified: / 01-02-2012 / 00:37:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!PointerReadStream methodsFor:'initialize-release'!

close
!

contentsSpecies
	^contentsSpecies
!

contentsSpecies: aClass
	contentsSpecies := aClass
!

length: anObject
	length := anObject
!

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

!PointerReadStream methodsFor:'private'!

streamingInsertInto: aWriteStream
	^length
		ifNil: [ self error: 'Cannot stream from an unbounded stream' ]
		ifNotNil: [ super streamingInsertInto: aWriteStream ]
!

streamingWriteInto: aWriteStream
	^length
		ifNil: [ self error: 'Cannot stream from an unbounded stream' ]
		ifNotNil: [ super streamingWriteInto: aWriteStream ]
! !

!PointerReadStream methodsFor:'seeking'!

++ anInteger

	| count |
	anInteger < 0 ifTrue: [ ^self -- anInteger negated ].
	count := self available ifNil: [ anInteger ] ifNotNil: [ :available | available min: anInteger ].
	position := position + anInteger.
	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
!

available

	^self length ifNotNil: [ super available ]
!

length
	^length
!

position
	^position
!

position: aPosition

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

!PointerReadStream methodsFor:'testing'!

isPositionable
	^true
! !

!PointerReadStream class methodsFor:'documentation'!

version_SVN
    ^ '$Id$'
! !