terminals/extensions.st
author Martin Kobetic
Sun, 17 Nov 2013 00:22:31 -0500
changeset 144 e193a6772be4
parent 137 ef21c6ae6329
permissions -rw-r--r--
merging

"{ 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

    | handle |
    handle := OperatingSystem open: self osNameForAccess attributes: #(O_APPEND O_CREAT) mode: nil.
    ^(Xtreams::FileWriteStream on: handle)
	setFilename: self;
	position: self fileSize;
	isPositionable: false;
	yourself
! !

!Filename methodsFor:'converting'!

reading

	self isDirectory ifFalse: [ | handle |
	    handle := OperatingSystem open: self osNameForAccess attributes: #(O_RDONLY) mode: nil.
	    ^(Xtreams::FileReadStream on: handle)
		setFilename: self;
		yourself ].

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

!Filename methodsFor:'converting'!

writing

    | handle |
    handle := OperatingSystem open: self osNameForAccess attributes: #(O_WRONLY | O_CREAT) mode: nil.
    ^(Xtreams::FileWriteStream on: handle)
	setFilename: self;
	yourself
! !

!PipeStream methodsFor:'testing'!

isActive

    ^self isOpen
! !

!PipeStream methodsFor:'converting'!

reading

    ^Xtreams::ExternalReadStream on: self
! !

!PipeStream methodsFor:'converting'!

writing

    ^Xtreams::ExternalWriteStream on: self
! !

!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
	^Xtreams::ExternalReadStream on: self
! !

!Socket methodsFor:'converting'!

writing
	^Xtreams::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_HG

    ^ '$Changeset: <not expanded> $'
! !