terminals/extensions.sav
author mkobetic
Sun, 15 Jan 2012 02:18:17 +0000
changeset 39 80fdc4602b14
child 43 b9a077d6ce14
permissions -rw-r--r--
sockets and files

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

!

!Block methodsFor:'converting'!

reading
        self numArgs = 0 ifTrue: [^Xtreams::BlockClosureReadStream on: self].
        self numArgs = 1 ifTrue: [^Xtreams::BlockClosureGenerateStream on: self].
        self error: 'More arguments than we can poke a stick at!!'
! !
!Block methodsFor:'converting'!

writing
        self numArgs = 1 ifTrue: [^Xtreams::BlockClosureWriteStream on: self].
        self error: 'Must be a single argument block.'
! !
!Collection methodsFor:'converting'!

writing
        ^Xtreams::CollectionWriteStream on: self
! !
!Filename methodsFor:'converting'!

appending
	^(IOAccessor openFileNamed: self direction: IOAccessor appendOnly creation: IOAccessor mayCreate) writing
		position: self fileSize;
		isPositionable: false;
		yourself
! !
!Filename methodsFor:'converting'!

reading
	self isDirectory ifFalse: [^(IOAccessor openFileNamed: self direction: IOAccessor readOnly creation: IOAccessor noCreate) reading].

	"Return the directory contents as a stream of filenames"
	^([self directoryContents]
		on:	self errorReporter errorSignal
		do:	[:ex | ex return: #()])
			reading collecting: [:each | self construct: each asFilename]
! !
!Filename methodsFor:'converting'!

writing
	^(IOAccessor openFileNamed: self direction: IOAccessor writeOnly creation: IOAccessor mayCreate) writing
! !
!Random methodsFor:'converting'!

reading
	^[self next] reading
		contentsSpecies: self contentsSpecies;
		yourself
! !
!SequenceableCollection methodsFor:'converting'!

reading
        ^Xtreams::SequenceableCollectionReadStream on: self
! !
!SequenceableCollection methodsFor:'converting'!

writing
        ^Xtreams::SequenceableCollectionWriteStream on: self
! !
!SharedQueue methodsFor:'converting'!

reading
        ^Xtreams::SharedQueueReadStream on: self
! !
!SharedQueue methodsFor:'converting'!

writing
        ^Xtreams::SharedQueueWriteStream on: self
! !
!Socket methodsFor:'converting'!

accepting
	"Return a read stream that produces new sockets from incoming connections."

	"^	ReadStream"

	"Listen for connections and close those connections immediately.
	| socket |
	socket := SocketAccessor newTCP.
	socket listenFor: 1.
	[socket acceping do: [:client | client close]]
		ensure: [socket close]
	"

	^[self accept] reading
		closeBlock: [self close];
		yourself
! !
!Socket methodsFor:'converting'!

reading
	^ExternalReadStream on: self
! !
!Socket methodsFor:'converting'!

writing
	^ExternalWriteStream on: self
! !
!TextCollector methodsFor:'converting'!

writing
	^[:object | self nextPut: object] writing
! !
!UndefinedObject methodsFor:'converting'!

writing
        ^Xtreams::NullWriteStream new
! !
!Xtreams::Buffer methodsFor:'converting'!

reading
	^BufferReadStream on: self
! !
!Xtreams::Buffer methodsFor:'converting'!

writing
	^BufferWriteStream on: self
! !
!Xtreams::WriteStream methodsFor:'transforming'!

buffering: bufferSize
	"Delays committing its content to its underlying stream until it has reached a certain size ,#flush is sent, or the stream is closed."
	"       bufferSize      <Integer> The size of the buffer to start with.
		^<PositionWriteStream>"
	"
		(ByteArray new writing buffering: 5)
			write: (ByteArray withAll: (1 to: 11));
			conclusion
	"
	^BufferedWriteStream on: self bufferSize: bufferSize
! !
!stx_goodies_xtreams_terminals class methodsFor:'documentation'!

extensionsVersion_SVN
    ^ '$Id: extensions.st 17 2011-11-21 06:03:03Z mkobetic $'
! !