sockets and files
authormkobetic
Sun, 15 Jan 2012 02:18:53 +0000
changeset 40 9cf7a05861e6
parent 39 80fdc4602b14
child 41 af7ad50a8f62
sockets and files
transforms/Xtreams__ASCIIEncoder.st
transforms/Xtreams__CollectReadStream.st
transforms/Xtreams__CollectWriteStream.st
transforms/Xtreams__DuplicateReadStream.st
transforms/Xtreams__DuplicateWriteStream.st
transforms/Xtreams__EncodeReadStream.st
transforms/Xtreams__EncodeWriteStream.st
transforms/Xtreams__ISO8859L1Encoder.st
transforms/Xtreams__InterpretedReadStream.st
transforms/Xtreams__InterpretedWriteStream.st
transforms/Xtreams__MessagePackMarshaler.st
transforms/Xtreams__ObjectAnalyseStream.st
transforms/Xtreams__ObjectMarshaler.st
transforms/Xtreams__ObjectReadStream.st
transforms/Xtreams__ObjectWriteStream.st
transforms/Xtreams__TransformReadStream.st
transforms/Xtreams__TransformWriteStream.st
transforms/extensions.sav
transforms/extensions.st
transforms/stx_goodies_xtreams_transforms.st
transforms/tests/Xtreams__DuplicateTest.st
transforms/tests/Xtreams__InterpretingStreamTest.st
transforms/tests/Xtreams__MessagePackMarshalerTest.st
transforms/tests/Xtreams__ObjectMarshalerTest.st
transforms/tests/extensions.sav
transforms/tests/extensions.st
transforms/tests/stx_goodies_xtreams_transforms_tests.st
--- a/transforms/Xtreams__ASCIIEncoder.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__ASCIIEncoder.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
--- a/transforms/Xtreams__CollectReadStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__CollectReadStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
@@ -5,7 +7,7 @@
 ReadStream subclass:#CollectReadStream
 	instanceVariableNames:'block cache contentsSpecies direct'
 	classVariableNames:''
-	poolDictionaries:'Xtreams::XtreamsPool'
+	poolDictionaries:'XtreamsPool'
 	category:'Xtreams-Transforms'
 !
 
--- a/transforms/Xtreams__CollectWriteStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__CollectWriteStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
@@ -5,7 +7,7 @@
 WriteStream subclass:#CollectWriteStream
 	instanceVariableNames:'block cache'
 	classVariableNames:''
-	poolDictionaries:'Xtreams::XtreamsPool'
+	poolDictionaries:'XtreamsPool'
 	category:'Xtreams-Transforms'
 !
 
@@ -79,11 +81,11 @@
 
 contentsSpecies: aClass
 
-        cache ifNotNil: [ cache recycle ].
-        cache := aClass newRecycled: (
-                                (cache notNil and: [ cache size > 0 ])
-                                        ifTrue: [cache size]
-                                        ifFalse: [DefaultBufferSize])
+	cache ifNotNil: [ cache recycle ].
+	cache := aClass newRecycled: (
+				(cache notNil and: [ cache size > 0 ])
+					ifTrue: [cache size]
+					ifFalse: [DefaultBufferSize])
 !
 
 on: aDestination block: aBlock
--- a/transforms/Xtreams__DuplicateReadStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__DuplicateReadStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
--- a/transforms/Xtreams__DuplicateWriteStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__DuplicateWriteStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
--- a/transforms/Xtreams__EncodeReadStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__EncodeReadStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
@@ -6,7 +8,7 @@
 	instanceVariableNames:'transparent crPreceeding encoder buffer bufferWriting
 		bufferReading'
 	classVariableNames:''
-	poolDictionaries:'Xtreams::XtreamsPool'
+	poolDictionaries:'XtreamsPool'
 	category:'Xtreams-Transforms'
 !
 
--- a/transforms/Xtreams__EncodeWriteStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__EncodeWriteStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
@@ -6,7 +8,7 @@
 	instanceVariableNames:'encoder buffer bufferReading bufferWriting decodedLineEnd
 		encodedLineEnd'
 	classVariableNames:''
-	poolDictionaries:'Xtreams::XtreamsPool'
+	poolDictionaries:'XtreamsPool'
 	category:'Xtreams-Transforms'
 !
 
--- a/transforms/Xtreams__ISO8859L1Encoder.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__ISO8859L1Encoder.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
--- a/transforms/Xtreams__InterpretedReadStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__InterpretedReadStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
@@ -5,7 +7,7 @@
 ReadStream subclass:#InterpretedReadStream
 	instanceVariableNames:'elementSize cache cacheSize operation contentsSpecies'
 	classVariableNames:''
-	poolDictionaries:'Xtreams::XtreamsPool'
+	poolDictionaries:'XtreamsPool'
 	category:'Xtreams-Transforms'
 !
 
--- a/transforms/Xtreams__InterpretedWriteStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__InterpretedWriteStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
@@ -5,7 +7,7 @@
 WriteStream subclass:#InterpretedWriteStream
 	instanceVariableNames:'elementSize cache cacheSize operation contentsSpecies'
 	classVariableNames:''
-	poolDictionaries:'Xtreams::XtreamsPool'
+	poolDictionaries:'XtreamsPool'
 	category:'Xtreams-Transforms'
 !
 
--- a/transforms/Xtreams__MessagePackMarshaler.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__MessagePackMarshaler.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
@@ -5,7 +7,7 @@
 Object subclass:#MessagePackMarshaler
 	instanceVariableNames:'unmarshaling marshaling analysing'
 	classVariableNames:''
-	poolDictionaries:'Xtreams::XtreamsPool'
+	poolDictionaries:'XtreamsPool'
 	category:'Xtreams-Transforms'
 !
 
--- a/transforms/Xtreams__ObjectAnalyseStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__ObjectAnalyseStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
--- a/transforms/Xtreams__ObjectMarshaler.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__ObjectMarshaler.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
@@ -5,7 +7,7 @@
 Object subclass:#ObjectMarshaler
 	instanceVariableNames:'classes read write version rehash analyse immediate classesMutex'
 	classVariableNames:''
-	poolDictionaries:'Xtreams::XtreamsPool'
+	poolDictionaries:'XtreamsPool'
 	category:'Xtreams-Transforms'
 !
 
--- a/transforms/Xtreams__ObjectReadStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__ObjectReadStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
--- a/transforms/Xtreams__ObjectWriteStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__ObjectWriteStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
--- a/transforms/Xtreams__TransformReadStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__TransformReadStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
@@ -5,7 +7,7 @@
 ReadStream subclass:#TransformReadStream
 	instanceVariableNames:'buffer bufferWriting sourceAtEnd block closeBlock'
 	classVariableNames:''
-	poolDictionaries:'Xtreams::XtreamsPool'
+	poolDictionaries:'XtreamsPool'
 	category:'Xtreams-Transforms'
 !
 
--- a/transforms/Xtreams__TransformWriteStream.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/Xtreams__TransformWriteStream.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
 "{ NameSpace: Xtreams }"
@@ -6,7 +8,7 @@
 	instanceVariableNames:'buffer block closeBlock process incompleteCount readReady
 		writeReady closeReady'
 	classVariableNames:''
-	poolDictionaries:'Xtreams::XtreamsPool'
+	poolDictionaries:'XtreamsPool'
 	category:'Xtreams-Transforms'
 !
 
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/transforms/extensions.sav	Sun Jan 15 02:18:53 2012 +0000
@@ -0,0 +1,682 @@
+"{ Package: 'stx:goodies/xtreams/transforms' }"
+
+!
+
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+collecting: aBlock
+	"Transform each element using #collect: style block."
+	"	aBlock	<BlockClosure>	a #collect: style block used to tranform each element
+		^<CollectReadSteam>
+	""
+		((1 to: 5) reading collecting: [ :e | e * e ]) rest
+	""
+		((65 to: 90) reading collecting: [ :e | e asCharacter ]) contentsSpecies: String; rest
+	"
+	^CollectReadStream on: self block: aBlock
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+depairing
+	"Transform a stream of associations in to a stream of elements made up of the key and value association components."
+
+	^self transforming: [:in :out |
+		| association |
+		association := in get.
+		out put: association key.
+		out put: association value]
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+doing: aBlock
+	"Perform and action with each passing element using #do: style block."
+	"	aBlock	<BlockClosure>	a #do: style block invoked with each element as it passes through the stream
+		^<CollectReadSteam>
+	""
+		((1 to: 5) reading doing: [ :e | Transcript space; print: e * e ]) rest
+	"
+	^self collecting: [:each | (aBlock value: each). each]
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+duplicating: aWriteStream
+	"Duplicate all the contents written into @aWriteStream"
+	"	aWriteStream <WriteStream>	a stream to copy into
+		^<DuplicatingReadSteam>
+	""
+		| copy |
+		copy := ByteArray new writing.
+		((0 to: 15) reading duplicating: copy) rest -> copy conclusion
+	"
+	^DuplicateReadStream on: self duplicate: aWriteStream
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+encoding: anEncoding
+	"Transform bytes into characters using @anEncoding such as #utf8 or #ascii, etc. Any encoding supported by StreamEncoder is allowed.
+	The encoding steam also performs automatic line end conversion from arbitrary platform convention to CRs, unless set into a transparent mode"
+	"	anEncoding	<Symbol> encoding identifier recognized by StreamEncoder class>>new:
+		^<EncodedReadStream>
+	""
+		((65 to: 90) reading encoding: #ascii) rest
+	""
+		| crlf text |
+		crlf := String with: Character cr with: Character lf.
+		text := ('Hello', crlf, 'World') asByteArrayEncoding: #ascii.
+		(text reading encoding: #ascii) rest.
+		(text reading encoding: #ascii) setLineEndTransparent; rest
+	"
+	^EncodeReadStream on: self encoding: anEncoding
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+encodingBase64
+	"Decodes characters of base-64 encoding into bytes. Ignores any intervening whitespace.
+	Automatically ends the stream if it encounters final padding characters $=."
+	"	^<TransformReadStream>"
+	"
+		'AAECAwQFBgcICQo= and the rest should be ignored' reading encodingBase64 rest
+	"
+	| map cache |
+	map := [ :char | ('ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/' indexOf: char) - 1 ].
+	cache := ByteString new: 4.
+	^(self transforming: [ :in :out || count end block filter |
+		filter := in rejecting: #isSeparator.
+		count := [ filter read: 4 into: cache at: 1. 4 ] on: Incomplete do: [ :incomplete | incomplete count].
+		count isZero ifTrue: [ Incomplete zero raise ].
+		(end := cache indexOf: $=) isZero ifFalse: [ count := count min: end - 1 ].
+		count < 2 ifTrue: [ Incomplete zero signal ].
+		block := (1 to: 4) inject: 0 into: [ :total :i || sextet |
+			sextet := count < i ifTrue: [ 0 ] ifFalse: [ map value: (cache at: i) ].
+			sextet negative ifTrue: [ count := i ].
+			(total bitShift: 6) + sextet ].
+		2 to: count do: [ :i | out put: ((block bitShift: (i - 4) * 8) bitAnd: 255) ].
+		count < 4 ifTrue: [ (Incomplete count: count) raise ] ])
+			buffer: (RingBuffer on: (ByteArray new: 3));
+			yourself
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+encodingHex
+	"Decodes bytes hex characters."
+	"	^<TransformReadStream>"
+	"
+		(ByteArray withAll: (1 to: 20)) reading encodingHex rest
+	"
+	| i2c |
+	i2c := [ :i | '0123456789abcdef' at: i + 1 ].
+	^(self transforming: [ :in :out || byte |
+		byte := in get.
+		out put: (i2c value: (byte bitShift: -4)).
+		out put: (i2c value: (byte bitAnd: 15)) ])
+		contentsSpecies: ByteString;
+		yourself
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+injecting: initialObject into: aBlock
+	"Accumulates a running value combined with each passing element using the binary aBlock. aBlock takes the result of the last evaluation and the next element as its arguments. Notable difference from the collection analog is that the streaming variant is a stream of all the intermediate values of the running value."
+	"	initialObject	<Object> initial value used as the previous result for the evaluation of the first element
+		aBlock	<BlockClosure> binary block combining the value of each element with previous result of its evaluation
+		^<CollectingReadStream>"
+	"
+		((1 to: 10) reading injecting: 0 into: [ :total :each | each + total ]) rest
+	"
+	| nextObject |
+	nextObject := initialObject.
+	^self collecting: [:each | nextObject := aBlock cull: nextObject cull: each]
+! !
+!Xtreams::ReadStream methodsFor:'interpreting'!
+
+interpreting: type
+	"Converts bytes from a binary source according to provided @type. It produces elements of corresponding class, e.g. #float -> Float, #double -> Double, etc. Supported types are defined by the Interpretations shared class variable.
+	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
+		^		<InterpretedReadStream>
+	""
+		| doubles bytes |
+		doubles := [ Random new next ] reading.
+		bytes := (ByteArray new writing interpreting: #double)
+			write: 10 from: doubles;
+			close;
+			terminal.
+		(bytes reading interpreting: #double) read: 10
+	"
+	^self interpreting: type cacheSize: 1
+! !
+!Xtreams::ReadStream methodsFor:'interpreting'!
+
+interpreting: type cacheSize: size
+	"Converts bytes from a binary source according to provided @type. It produces elements of corresponding class, e.g. #float -> Float, #double -> Double, etc. Supported types are defined on class side of InterpretedBytes.
+	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via InterpretatedBytes)
+		size		<Integer>	requested cache size (in number of elements)
+		^		<InterpretedReadStream>
+	""
+		| doubles bytes |
+		doubles := [ Random new next ] reading.
+		bytes := (ByteArray new writing interpreting: #double cacheSize: 10)
+			write: 10 from: doubles;
+			close;
+			terminal.
+		(bytes reading interpreting: #double) read: 10
+	"
+	^InterpretedReadStream on: self type: type cacheSize: size
+! !
+!Xtreams::ReadStream methodsFor:'interpreting'!
+
+interpreting: reader size: byteSize
+	"Converts bytes from a binary source according to provided @reader block. The block is evaluated with an instance of InterpretedBytes and and index into it from which it should use byteSize bytes to make an object to return.
+	""	reader		<BlockClosure>	reading block, e.g. [ :b :i | (b at: i) @ (b at: i + 1) ]
+		byteSize	<Integer>	byte size of an element
+		^			<InterpretedReadStream>
+	""
+		| doubles bytes |
+		doubles := [ Random new next ] reading.
+		bytes := (ByteArray new writing interpreting: #double)
+			write: 10 from: doubles;
+			close;
+			terminal.
+		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8) read: 5
+	"
+	^InterpretedReadStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: reader cacheSize: 1
+! !
+!Xtreams::ReadStream methodsFor:'interpreting'!
+
+interpreting: reader size: byteSize cacheSize: cacheSize
+	"Converts bytes from a binary source according to provided @reader block. The block is evaluated with an instance of InterpretedBytes and and index into it from which it should use byteSize bytes to make an object to return.
+	""	reader		<BlockClosure>	reading block, e.g. [ :b :i | (b at: i) @ (b at: i + 1) ]
+		byteSize	<Integer>	byte size of an element
+		cacheSize	<Integer>	requested cache size (in number of elements)
+		^			<InterpretedReadStream>
+	""
+		| points bytes |
+		points := Random new reading transforming: [ :in :out | out put: in get @ in get ].
+		bytes := (ByteArray new writing interpreting: [ :b :i :o | (b floatAt: i put: o x) @ (b floatAt: i + 4 put: o y) ] size: 8 )
+			write: 10 from: points;
+			close;
+			terminal.
+		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8 cacheSize: 5) read: 5
+	"
+	^InterpretedReadStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: reader cacheSize: cacheSize
+! !
+!Xtreams::ReadStream methodsFor:'interpreting'!
+
+marshaling
+	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID. A marshaling read stream decodes objects from a binary source previously encoded by a marshaling write stream.
+	""	^	<ObjectReadSteam>
+	""
+		| rectangle bytes |
+		rectangle := 5 @ 5 extent: 5 @ 5.
+		bytes := ByteArray new writing marshaling put: rectangle; conclusion.
+		bytes reading marshaling get
+	"
+	^ObjectReadStream on: self
+! !
+!Xtreams::ReadStream methodsFor:'interpreting'!
+
+marshaling: aMarshaler
+	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID. Custom marshaling schemes can be derived by subclassing ObjectMarshaler. Custom schemes must declare their own (unique) version ID. This method allows to employ a cusomt marshaler instead of the default one (STST2.0).
+	A marshaling read stream decodes objects from a binary source previously encoded by a marshaling write stream.
+	""	aMarshaler	<ObjectMarshaler>	implements custom marshaling format
+		^			<ObjectReadSteam>
+	""
+		| rectangle bytes |
+		rectangle := 5 @ 5 extent: 5 @ 5.
+		bytes := (ByteArray new writing marshaling: ObjectMarshaler new) put: rectangle; conclusion.
+		bytes reading marshaling get
+	"
+	^ObjectReadStream on: self marshaler: aMarshaler
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+monitoring: aNotificationBlock every: aNotificationInterval
+	"Monitor the through-put of the receiver."
+	"	aNotificationBlock <BlockClosure>	the block to execute when notifying
+		aNotificationInterval <Duration>	how often to notify
+		^<PositionReadSubstream>
+	"
+
+	"
+		| monitor |
+		monitor := ObjectMemory imageFilename reading
+			monitoring: [:totalTransferred :deltaTransferred :elapsedMicroseconds |
+				throughputSpeed := deltaTransferred.
+				averageSpeed := (totalTransferred / elapsedMicroseconds) * 1000000.
+				Transcript writing cr;
+					write: 'average speed: '; print: averageSpeed asFloat;
+					write: ' through-put speed: '; print: throughputSpeed asFloat;
+					write: ' elapsed-time: '; print: elapsedMicroseconds / 1000000.0]
+			every: 1 milliseconds.
+		[monitor rest] ensure: [monitor close].
+	"
+
+	| previousPosition timer start notifyBlock monitoring notifyProcess notifyFinished |
+
+	start := Time microsecondClock.
+	previousPosition := 0.
+	monitoring := nil.
+	timer := nil.
+	notifyFinished := false.
+
+	notifyBlock := [
+		aNotificationBlock cull: monitoring position cull: monitoring position - previousPosition cull: Time microsecondClock - start.
+		previousPosition := monitoring position].
+
+	notifyProcess := nil.
+	notifyProcess := [
+		[notifyBlock value. notifyFinished] whileFalse: [notifyProcess suspend]] newProcess.
+	notifyProcess priority: ((Processor activeProcess priority + 1) min: 99).
+
+	monitoring := self closing: [
+		timer stop.
+		notifyProcess resume.
+		notifyFinished := true.
+		notifyProcess resume.
+		self close].
+
+	timer := Timer every: aNotificationInterval resume: notifyProcess.
+	^monitoring
+! !
+!Xtreams::ReadStream methodsFor:'private'!
+
+next
+	"This is here for compatibility with the existing StreamEncoders so that they can be re-used with transformation streams for encoding."
+
+	^self get
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+pairing
+	"Transform a stream of elements in to a stream of associations between even+odd elements of the stream. This expects the stream to have an even number of elements"
+
+	^self transforming: [:in :out | out put: (Association key: in get value: in get)]
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+rejecting: aBlock
+	"Filters elements from the source using aBlock. aBlock has the same form and semantics as the #reject: block on collections."
+	"	aBlock	<BlockClosure>	usual #reject: style block used to filter the elements passing through
+		^<TransformReadStream>"
+	"
+		((1 to: 10) reading rejecting: [ :e | e odd ]) rest
+	"
+	^self transforming: [:input :output |
+		| value |
+		[value := input get.
+		aBlock cull: value] whileTrue.
+		output put: value]
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+selecting: aBlock
+	"Filters elements from the source using aBlock. aBlock has the same form and semantics as the #select: block on collections."
+	"	aBlock	<BlockClosure>	usual #select: style block used to filter the elements passing through
+		^<TransformReadStream>"
+	"
+		((1 to: 10) reading selecting: [ :e | e odd ]) rest
+	"
+	^self transforming: [:input :output |
+		| value |
+		[value := input get.
+		aBlock cull: value] whileFalse.
+		output put: value]
+! !
+!Xtreams::ReadStream methodsFor:'transforming'!
+
+transforming: aBlock
+	"This is the most general form of transform stream. The block receives two streams, the source (input) and a virtual stream of elements to be produced by the stream (output). The block can read arbitrary number of elements from input (including none) and write arbitrary number of elements into the output (including none). The block will be invoked as many times as necessary to produce the required number of elements, or until an Incomplete is raised. Consequently if the block handles Incomplete from the input, it has to raise another Incomplete at some point, otherwise the stream will never end.
+	Note that if the contentSpecies of the source doesn't fit the output of the transformation, the contents species of the transform stream has to be set explicitly.
+	""	aBlock	<BlockClosure>	binary transformation block that reads elements from input (first argument) and writes elements into output (second argument)
+		^<TransformReadStream>
+	""	Convert text into a stream of words
+		('hello world!! bye world!!' reading transforming: [ :in :out || word char |
+			word := String new writing.
+			[	[  (char := in get) = Character space ] whileFalse: [ word put: char ].
+			] ensure: [ out put: (word close; destination) ] ]
+		)	contentsSpecies: Array;
+			rest
+	""	Convert a hex-string into a byte array (2 characters per byte)
+		| c2d |
+		c2d := [ :char | ('0123456789abcdef' indexOf: char) - 1 ].
+		('0123456789abcdef' reading transforming: [ :in :out |
+			out put: (c2d value: in get) * 16 + (c2d value: in get) ]
+		)	buffer: (RingBuffer on: (ByteArray new: 1));
+			rest
+	"
+	^TransformReadStream on: self block: aBlock
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+collecting: aBlock
+	"Transform each written element using #collect: style block."
+	"	aBlock	<BlockClosure>	a #collect: style block used to tranform each element
+		^<CollectWriteSteam>
+	""
+		(Array new writing collecting: [ :e | e * e ]) write: (1 to: 5); conclusion
+	""
+		(String new writing collecting: [ :e | e asCharacter ]) write: (65 to: 90); conclusion
+	"
+	^CollectWriteStream on: self block: aBlock
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+depairing
+	"Transform a stream of associations in to a stream of elements made up of the key and value association components."
+
+	^self transforming: [:in :out |
+		| association |
+		association := in get.
+		out put: association key.
+		out put: association value]
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+doing: aBlock
+	"Perform and action with each passing element using #do: style block."
+	"	aBlock	<BlockClosure>	a #do: style block invoked with each element as it passes through the stream
+		^<CollectWriteSteam>
+	""
+		(Array new writing doing: [ :e | Transcript space; print: e * e ]) write: (1 to: 10); conclusion
+	"
+	^self collecting: [:each | (aBlock value: each). each]
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+duplicating: aWriteStream
+	"Duplicate all the contents written into @aWriteStream"
+	"	aWriteStream <WriteStream>	a stream to copy into
+		^<DuplicateWriteSteam>
+	""
+		| original copy |
+		original := Array new writing.
+		copy := ByteArray new writing.
+		(original duplicating: copy) write: (0 to: 15).
+		original conclusion -> copy conclusion
+	"
+	^DuplicateWriteStream on: self duplicate: aWriteStream
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+encoding: anEncoding
+	"Transform characters into bytes using @anEncoding such as #utf8 or #ascii, etc. Any encoding supported by StreamEncoder is allowed.
+	The encoding steam also performs automatic conversion of CRs into the native line-end convention of the underlying platform,
+	unless set into a different line-end convention mode"
+	"	anEncoding	<Symbol> encoding identifier recognized by StreamEncoder class>>new:
+		^<EncodedWriteStream>
+	""
+		(ByteArray new writing encoding: #ascii) write: 'abcdefghi'; conclusion
+	""
+		(ByteArray new writing encoding: #ascii) write: 'Hello\World' withCRs; conclusion
+	""
+		(ByteArray new writing encoding: #ascii) setLineEndCRLF; write: 'Hello\World' withCRs; conclusion
+	"
+	^EncodeWriteStream on: self encoding: anEncoding
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+encodingBase64
+	"Encodes bytes into characters of base-64 encoding.
+	Emits final padding characters ($=) as required, when the stream is closed."
+	"	^<TransformWriteStream>"
+	"
+		String new writing encodingBase64 write: (ByteArray withAll: (1 to: 20)); conclusion
+	"
+	| map cache |
+	map := [ :i | 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/' at: i + 1 ].
+	cache := ByteArray new: 3.
+	^(self transforming: [ :in :out | | count block shift |
+		count := [ in read: 3 into: cache at: 1. 3 ] on: Incomplete do: [ :incomplete | incomplete count].
+		count isZero ifTrue: [ Incomplete zero raise ].
+		block := (1 to: count) inject: 0 into: [ :total :byte | (total bitShift: 8) + (cache at: byte)].
+		shift := count * -8.
+		1 to: count + 1 do: [:i | out put: (map value: ((block bitShift: (shift + (i * 6))) bitAnd: 63))].
+		count < 3 ifTrue: [
+			3 - count timesRepeat: [ out put: $= ].
+			(Incomplete count: count) raise]])
+		buffer: (RingBuffer on: (ByteArray new: 3));
+		yourself
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+encodingHex
+	"Encodes hex characters into bytes."
+	"	^<TransformReadStream>"
+	"
+		ByteArray new writing encodingHex write: '010203fdfeff'; terminal
+	"
+	| c2i |
+	c2i := [ :c | ('0123456789abcdef' indexOf: c asLowercase) - 1 ].
+	^(self transforming: [ :in :out |
+		out put: ((c2i value: in get) bitShift: 4) + (c2i value: in get) ])
+		contentsSpecies: ByteString;
+		yourself
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+injecting: initialObject into: aBlock
+	"Accumulates a running value combined with each passing element using the binary aBlock. aBlock takes the result of the last evaluation and the next element as arguments. Notable difference from the collection analog is that the streaming variant is a stream of all the intermediate values of the running value."
+	"	initialObject	<Object> initial value used as the previous result for the evaluation of the first element
+		aBlock	<BlockClosure> binary block combining the value of each element with previous result of its evaluation
+		^<CollectingWriteStream>"
+	"
+		(Array new writing injecting: 0 into: [ :total :each | each + total ]) write: (1 to: 10); conclusion
+	"
+	| nextObject |
+	nextObject := initialObject.
+	^self collecting: [:each | nextObject := aBlock cull: nextObject cull: each]
+! !
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+interpreting: type
+	"Converts consumed elements into bytes of pre-configured (primitive) CType, e.g. float, long etc. The type of the written elements must match the CType and the underlying destination must be binary.
+	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
+		^		<InterpretedWriteStream>
+	""
+		| doubles bytes |
+		doubles := [ Random new next ] reading.
+		bytes := (ByteArray new writing interpreting: #double)
+			write: 10 from: doubles;
+			close;
+			terminal.
+		(bytes reading interpreting: #double) read: 10
+	"
+	^self interpreting: type cacheSize: 1
+! !
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+interpreting: type cacheSize: size
+	"Converts consumed elements into bytes of pre-configured (primitive) CType, e.g. float, long etc. The type of the written elements must match the CType and the underlying destination must be binary.
+	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
+		size		<Integer>	requested buffer size (in number of elements)
+		^		<InterpretedWriteStream>
+	""
+		| doubles bytes |
+		doubles := [ Random new next ] reading.
+		bytes := (ByteArray new writing interpreting: #double size: 10)
+			write: 10 from: doubles;
+			close;
+			terminal.
+		(bytes reading interpreting: #double) read: 10
+	"
+	^InterpretedWriteStream on: self type: type cacheSize: size
+! !
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+interpreting: writer size: byteSize
+	"Converts objects into bytes in a binary destination according to provided @writer block. The block is evaluated with an instance of InterpretedBytes an index and object to write into the bytes.
+	""	type		<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
+		byteSize	<Integer>	byte size of an element
+		^			<InterpretedWriteStream>
+	""
+		| points bytes |
+		points := Random new reading transforming: [ :in :out | out put: in get @ in get ].
+		bytes := (ByteArray new writing interpreting: [ :b :i :o | (b floatAt: i put: o x) @ (b floatAt: i + 4 put: o y) ] size: 8 )
+			write: 10 from: points;
+			close;
+			terminal.
+		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8 cacheSize: 5) read: 5
+	"
+	^InterpretedWriteStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: writer cacheSize: 1
+! !
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+interpreting: writer size: byteSize cacheSize: cacheSize
+	"Converts objects into bytes in a binary destination according to provided @writer block. The block is evaluated with an instance of InterpretedBytes an index and object to write into the bytes.
+	""	type		<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
+		byteSize	<Integer>	byte size of an element
+		cacheSize	<Integer>	requested cache size (in number of elements)
+		^			<InterpretedWriteStream>
+	""
+		| points bytes |
+		points := Random new reading transforming: [ :in :out | out put: in get @ in get ].
+		bytes := (ByteArray new writing interpreting: [ :b :i :o | (b floatAt: i put: o x) @ (b floatAt: i + 4 put: o y) ] size: 8 )
+			write: 10 from: points;
+			close;
+			terminal.
+		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8 cacheSize: 5) read: 5
+	"
+	^InterpretedWriteStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: writer cacheSize: cacheSize
+! !
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+marshaling
+	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID.
+	A marshaling write stream encodes objects into a binary destination stream.
+	""	^			<ObjectWriteSteam>
+	""
+		| rectangle bytes |
+		rectangle := 5 @ 5 extent: 5 @ 5.
+		bytes := ByteArray new writing marshaling put: rectangle; conclusion.
+		bytes reading marshaling get
+	"
+	^ObjectWriteStream on: self
+! !
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+marshaling: aMarshaler
+	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID. Custom marshaling schemes can be derived by subclassing ObjectMarshaler. Custom schemes must declare their own (unique) version ID. This method allows to employ a cusomt marshaler instead of the default one (STST2.0).
+	A marshaling write stream encodes objects into a binary destination stream.
+	""	aMarshaler	<ObjectMarshaler>	implements custom marshaling format
+		^			<ObjectWriteSteam>
+	""
+		| rectangle bytes |
+		rectangle := 5 @ 5 extent: 5 @ 5.
+		bytes := (ByteArray new writing marshaling: ObjectMarshaler new) put: rectangle; conclusion.
+		bytes reading marshaling get
+	"
+	^ObjectWriteStream on: self marshaler: aMarshaler
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+monitoring: aNotificationBlock every: aNotificationInterval
+	"Monitor the through-put of the receiver."
+	"	aNotificationBlock <BlockClosure>	the block to execute when notifying
+		aNotificationInterval <Duration>	how often to notify
+		^<PositionWriteSubstream>
+	"
+
+	| previousPosition timer start notifyBlock monitoring notifyProcess notifyFinished |
+
+	start := Time microsecondClock.
+	previousPosition := 0.
+	monitoring := nil.
+	timer := nil.
+	notifyFinished := false.
+
+	notifyBlock := [
+		aNotificationBlock cull: monitoring position cull: monitoring position - previousPosition cull: Time microsecondClock - start.
+		previousPosition := monitoring position].
+
+	notifyProcess := nil.
+	notifyProcess := [
+		[notifyBlock value. notifyFinished] whileFalse: [notifyProcess suspend]] newProcess.
+	notifyProcess priority: ((Processor activeProcess priority + 1) min: 99).
+
+	monitoring := self closing: [
+		timer stop.
+		notifyProcess resume.
+		notifyFinished := true.
+		notifyProcess resume.
+		self close].
+
+	timer := Timer every: aNotificationInterval resume: notifyProcess.
+	^monitoring
+! !
+!Xtreams::WriteStream methodsFor:'private'!
+
+nextPut: anObject
+	"This is here for compatibility with the existing StreamEncoders so that they can be re-used with transformation streams for encoding."
+	self put: anObject.
+	^anObject
+! !
+!Xtreams::WriteStream methodsFor:'private'!
+
+nextPutAll: aCollection
+	"This is here for compatibility with the existing StreamEncoders so that they can be re-used with transformation streams for encoding."
+	self write: aCollection.
+	^aCollection
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+pairing
+	"Transform a stream of elements in to a stream of associations between even+odd elements of the stream. This expects the stream to have an even number of elements"
+
+	^self transforming: [:in :out | out put: (Association key: in get value: in get)]
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+rejecting: aBlock
+	"Filters written elements using aBlock. aBlock has the same form and semantics as the #reject: block on collections."
+	"	aBlock	<BlockClosure>	usual #reject: style block used to filter the elements passing through
+		^<TransformWriteStream>"
+	"
+		(Array new writing rejecting: [ :e | e odd ]) write: (1 to: 10); conclusion
+	"
+	^self selecting: [:each | (aBlock cull: each) not]
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+selecting: aBlock
+	"Filters written elements using aBlock. aBlock has the same form and semantics as the #select: block on collections."
+	"	aBlock	<BlockClosure>	usual #select: style block used to filter the elements passing through
+		^<TransformWriteStream>"
+	"
+		(Array new writing selecting: [ :e | e odd ]) write: (1 to: 10); conclusion
+	"
+	^self transforming: [:input :output |
+		| value |
+		[value := input get.
+		aBlock cull: value] whileFalse.
+		output put: value]
+! !
+!Xtreams::WriteStream methodsFor:'transforming'!
+
+transforming: aBlock
+	"This is the most general form of transform stream. The block receives two streams, a virtual stream of written elements (input) and the destination (output). The block can read arbitrary number of elements from input (including none) and write arbitrary number of elements into the output (including none). The block will be invoked as many times as necessary to consume any written elements, or until an Incomplete is raised by the destination.
+	Note that if the #contentSpecies of the destination doesn't fit the input of the transformation, the #contentsSpecies of the transform stream has to be set explicitly.
+	""	aBlock	<BlockClosure>	binary transformation block that reads elements from input (first argument) and writes elements into output (second argument)
+		^<TransformWriteStream>
+	""	Convert text into a stream of words
+		(Array new writing transforming: [ :in :out || word char |
+			word := String new writing.
+			[	[  (char := in get) = Character space ] whileFalse: [ word put: char ].
+			] ensure: [ out put: (word close; destination) ] ]
+		)	write: 'hello world!! bye world!!';
+			close;
+			terminal
+	""	Convert a hex-string into a byte array (2 characters per byte)
+		| c2d |
+		c2d := [ :char | ('0123456789abcdef' indexOf: char) - 1 ].
+		(ByteArray new writing transforming: [ :in :out |
+			out put: (c2d value: in get) * 16 + (c2d value: in get) ]
+		)	contentsSpecies: String;
+			write: '0123456789abcdef';
+			close;
+			terminal
+	"
+	^TransformWriteStream on: self block: aBlock
+! !
+!stx_goodies_xtreams_transforms class methodsFor:'documentation'!
+
+extensionsVersion_SVN
+    ^ '$Id: extensions.st 19 2011-11-21 06:04:06Z mkobetic $'
+! !
--- a/transforms/extensions.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/extensions.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,6 +1,119 @@
-"{ Package: 'stx:goodies/xtreams/transforms' }"
+"{ Encoding: utf8 }" !
+"{ Package: 'stx:goodies/xtreams/transforms' }" !
+
+!Xtreams::ReadStream methodsFor:'interpreting'!
+
+interpreting: type
+	"Converts bytes from a binary source according to provided @type. It produces elements of corresponding class, e.g. #float -> Float, #double -> Double, etc. Supported types are defined by the Interpretations shared class variable.
+	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
+		^		<InterpretedReadStream>
+	""
+		| doubles bytes |
+		doubles := [ Random new next ] reading.
+		bytes := (ByteArray new writing interpreting: #double)
+			write: 10 from: doubles;
+			close;
+			terminal.
+		(bytes reading interpreting: #double) read: 10
+	"
+	^self interpreting: type cacheSize: 1
+! !
+
+!Xtreams::ReadStream methodsFor:'interpreting'!
+
+interpreting: type cacheSize: size
+	"Converts bytes from a binary source according to provided @type. It produces elements of corresponding class, e.g. #float -> Float, #double -> Double, etc. Supported types are defined on class side of InterpretedBytes.
+	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via InterpretatedBytes)
+		size		<Integer>	requested cache size (in number of elements)
+		^		<InterpretedReadStream>
+	""
+		| doubles bytes |
+		doubles := [ Random new next ] reading.
+		bytes := (ByteArray new writing interpreting: #double cacheSize: 10)
+			write: 10 from: doubles;
+			close;
+			terminal.
+		(bytes reading interpreting: #double) read: 10
+	"
+	^InterpretedReadStream on: self type: type cacheSize: size
+! !
+
+!Xtreams::ReadStream methodsFor:'interpreting'!
 
-!
+interpreting: reader size: byteSize
+	"Converts bytes from a binary source according to provided @reader block. The block is evaluated with an instance of InterpretedBytes and and index into it from which it should use byteSize bytes to make an object to return.
+	""	reader		<BlockClosure>	reading block, e.g. [ :b :i | (b at: i) @ (b at: i + 1) ]
+		byteSize	<Integer>	byte size of an element
+		^			<InterpretedReadStream>
+	""
+		| doubles bytes |
+		doubles := [ Random new next ] reading.
+		bytes := (ByteArray new writing interpreting: #double)
+			write: 10 from: doubles;
+			close;
+			terminal.
+		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8) read: 5
+	"
+	^InterpretedReadStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: reader cacheSize: 1
+! !
+
+!Xtreams::ReadStream methodsFor:'interpreting'!
+
+interpreting: reader size: byteSize cacheSize: cacheSize
+	"Converts bytes from a binary source according to provided @reader block. The block is evaluated with an instance of InterpretedBytes and and index into it from which it should use byteSize bytes to make an object to return.
+	""	reader		<BlockClosure>	reading block, e.g. [ :b :i | (b at: i) @ (b at: i + 1) ]
+		byteSize	<Integer>	byte size of an element
+		cacheSize	<Integer>	requested cache size (in number of elements)
+		^			<InterpretedReadStream>
+	""
+		| points bytes |
+		points := Random new reading transforming: [ :in :out | out put: in get @ in get ].
+		bytes := (ByteArray new writing interpreting: [ :b :i :o | (b floatAt: i put: o x) @ (b floatAt: i + 4 put: o y) ] size: 8 )
+			write: 10 from: points;
+			close;
+			terminal.
+		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8 cacheSize: 5) read: 5
+	"
+	^InterpretedReadStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: reader cacheSize: cacheSize
+! !
+
+!Xtreams::ReadStream methodsFor:'interpreting'!
+
+marshaling
+	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID. A marshaling read stream decodes objects from a binary source previously encoded by a marshaling write stream.
+	""	^	<ObjectReadSteam>
+	""
+		| rectangle bytes |
+		rectangle := 5 @ 5 extent: 5 @ 5.
+		bytes := ByteArray new writing marshaling put: rectangle; conclusion.
+		bytes reading marshaling get
+	"
+	^ObjectReadStream on: self
+! !
+
+!Xtreams::ReadStream methodsFor:'interpreting'!
+
+marshaling: aMarshaler
+	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID. Custom marshaling schemes can be derived by subclassing ObjectMarshaler. Custom schemes must declare their own (unique) version ID. This method allows to employ a cusomt marshaler instead of the default one (STST2.0).
+	A marshaling read stream decodes objects from a binary source previously encoded by a marshaling write stream.
+	""	aMarshaler	<ObjectMarshaler>	implements custom marshaling format
+		^			<ObjectReadSteam>
+	""
+		| rectangle bytes |
+		rectangle := 5 @ 5 extent: 5 @ 5.
+		bytes := (ByteArray new writing marshaling: ObjectMarshaler new) put: rectangle; conclusion.
+		bytes reading marshaling get
+	"
+	^ObjectReadStream on: self marshaler: aMarshaler
+! !
+
+!Xtreams::ReadStream methodsFor:'private'!
+
+next
+	"This is here for compatibility with the existing StreamEncoders so that they can be re-used with transformation streams for encoding."
+
+	^self get
+! !
 
 !Xtreams::ReadStream methodsFor:'transforming'!
 
@@ -15,6 +128,7 @@
 	"
 	^CollectReadStream on: self block: aBlock
 ! !
+
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 depairing
@@ -26,6 +140,7 @@
 		out put: association key.
 		out put: association value]
 ! !
+
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 doing: aBlock
@@ -37,6 +152,7 @@
 	"
 	^self collecting: [:each | (aBlock value: each). each]
 ! !
+
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 duplicating: aWriteStream
@@ -50,6 +166,7 @@
 	"
 	^DuplicateReadStream on: self duplicate: aWriteStream
 ! !
+
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 encoding: anEncoding
@@ -68,6 +185,7 @@
 	"
 	^EncodeReadStream on: self encoding: anEncoding
 ! !
+
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 encodingBase64
@@ -95,6 +213,7 @@
 			buffer: (RingBuffer on: (ByteArray new: 3));
 			yourself
 ! !
+
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 encodingHex
@@ -112,6 +231,7 @@
 		contentsSpecies: ByteString;
 		yourself
 ! !
+
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 injecting: initialObject into: aBlock
@@ -126,106 +246,7 @@
 	nextObject := initialObject.
 	^self collecting: [:each | nextObject := aBlock cull: nextObject cull: each]
 ! !
-!Xtreams::ReadStream methodsFor:'interpreting'!
 
-interpreting: type
-	"Converts bytes from a binary source according to provided @type. It produces elements of corresponding class, e.g. #float -> Float, #double -> Double, etc. Supported types are defined by the Interpretations shared class variable.
-	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
-		^		<InterpretedReadStream>
-	""
-		| doubles bytes |
-		doubles := [ Random new next ] reading.
-		bytes := (ByteArray new writing interpreting: #double)
-			write: 10 from: doubles;
-			close;
-			terminal.
-		(bytes reading interpreting: #double) read: 10
-	"
-	^self interpreting: type cacheSize: 1
-! !
-!Xtreams::ReadStream methodsFor:'interpreting'!
-
-interpreting: type cacheSize: size
-	"Converts bytes from a binary source according to provided @type. It produces elements of corresponding class, e.g. #float -> Float, #double -> Double, etc. Supported types are defined on class side of InterpretedBytes.
-	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via InterpretatedBytes)
-		size		<Integer>	requested cache size (in number of elements)
-		^		<InterpretedReadStream>
-	""
-		| doubles bytes |
-		doubles := [ Random new next ] reading.
-		bytes := (ByteArray new writing interpreting: #double cacheSize: 10)
-			write: 10 from: doubles;
-			close;
-			terminal.
-		(bytes reading interpreting: #double) read: 10
-	"
-	^InterpretedReadStream on: self type: type cacheSize: size
-! !
-!Xtreams::ReadStream methodsFor:'interpreting'!
-
-interpreting: reader size: byteSize
-	"Converts bytes from a binary source according to provided @reader block. The block is evaluated with an instance of InterpretedBytes and and index into it from which it should use byteSize bytes to make an object to return.
-	""	reader		<BlockClosure>	reading block, e.g. [ :b :i | (b at: i) @ (b at: i + 1) ]
-		byteSize	<Integer>	byte size of an element
-		^			<InterpretedReadStream>
-	""
-		| doubles bytes |
-		doubles := [ Random new next ] reading.
-		bytes := (ByteArray new writing interpreting: #double)
-			write: 10 from: doubles;
-			close;
-			terminal.
-		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8) read: 5
-	"
-	^InterpretedReadStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: reader cacheSize: 1
-! !
-!Xtreams::ReadStream methodsFor:'interpreting'!
-
-interpreting: reader size: byteSize cacheSize: cacheSize
-	"Converts bytes from a binary source according to provided @reader block. The block is evaluated with an instance of InterpretedBytes and and index into it from which it should use byteSize bytes to make an object to return.
-	""	reader		<BlockClosure>	reading block, e.g. [ :b :i | (b at: i) @ (b at: i + 1) ]
-		byteSize	<Integer>	byte size of an element
-		cacheSize	<Integer>	requested cache size (in number of elements)
-		^			<InterpretedReadStream>
-	""
-		| points bytes |
-		points := Random new reading transforming: [ :in :out | out put: in get @ in get ].
-		bytes := (ByteArray new writing interpreting: [ :b :i :o | (b floatAt: i put: o x) @ (b floatAt: i + 4 put: o y) ] size: 8 )
-			write: 10 from: points;
-			close;
-			terminal.
-		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8 cacheSize: 5) read: 5
-	"
-	^InterpretedReadStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: reader cacheSize: cacheSize
-! !
-!Xtreams::ReadStream methodsFor:'interpreting'!
-
-marshaling
-	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID. A marshaling read stream decodes objects from a binary source previously encoded by a marshaling write stream.
-	""	^	<ObjectReadSteam>
-	""
-		| rectangle bytes |
-		rectangle := 5 @ 5 extent: 5 @ 5.
-		bytes := ByteArray new writing marshaling put: rectangle; conclusion.
-		bytes reading marshaling get
-	"
-	^ObjectReadStream on: self
-! !
-!Xtreams::ReadStream methodsFor:'interpreting'!
-
-marshaling: aMarshaler
-	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID. Custom marshaling schemes can be derived by subclassing ObjectMarshaler. Custom schemes must declare their own (unique) version ID. This method allows to employ a cusomt marshaler instead of the default one (STST2.0).
-	A marshaling read stream decodes objects from a binary source previously encoded by a marshaling write stream.
-	""	aMarshaler	<ObjectMarshaler>	implements custom marshaling format
-		^			<ObjectReadSteam>
-	""
-		| rectangle bytes |
-		rectangle := 5 @ 5 extent: 5 @ 5.
-		bytes := (ByteArray new writing marshaling: ObjectMarshaler new) put: rectangle; conclusion.
-		bytes reading marshaling get
-	"
-	^ObjectReadStream on: self marshaler: aMarshaler
-! !
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 monitoring: aNotificationBlock every: aNotificationInterval
@@ -276,13 +297,7 @@
 	timer := Timer every: aNotificationInterval resume: notifyProcess.
 	^monitoring
 ! !
-!Xtreams::ReadStream methodsFor:'private'!
 
-next
-	"This is here for compatibility with the existing StreamEncoders so that they can be re-used with transformation streams for encoding."
-
-	^self get
-! !
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 pairing
@@ -290,6 +305,7 @@
 
 	^self transforming: [:in :out | out put: (Association key: in get value: in get)]
 ! !
+
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 rejecting: aBlock
@@ -305,6 +321,7 @@
 		aBlock cull: value] whileTrue.
 		output put: value]
 ! !
+
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 selecting: aBlock
@@ -320,6 +337,7 @@
 		aBlock cull: value] whileFalse.
 		output put: value]
 ! !
+
 !Xtreams::ReadStream methodsFor:'transforming'!
 
 transforming: aBlock
@@ -344,6 +362,130 @@
 	"
 	^TransformReadStream on: self block: aBlock
 ! !
+
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+interpreting: type
+	"Converts consumed elements into bytes of pre-configured (primitive) CType, e.g. float, long etc. The type of the written elements must match the CType and the underlying destination must be binary.
+	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
+		^		<InterpretedWriteStream>
+	""
+		| doubles bytes |
+		doubles := [ Random new next ] reading.
+		bytes := (ByteArray new writing interpreting: #double)
+			write: 10 from: doubles;
+			close;
+			terminal.
+		(bytes reading interpreting: #double) read: 10
+	"
+	^self interpreting: type cacheSize: 1
+! !
+
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+interpreting: type cacheSize: size
+	"Converts consumed elements into bytes of pre-configured (primitive) CType, e.g. float, long etc. The type of the written elements must match the CType and the underlying destination must be binary.
+	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
+		size		<Integer>	requested buffer size (in number of elements)
+		^		<InterpretedWriteStream>
+	""
+		| doubles bytes |
+		doubles := [ Random new next ] reading.
+		bytes := (ByteArray new writing interpreting: #double size: 10)
+			write: 10 from: doubles;
+			close;
+			terminal.
+		(bytes reading interpreting: #double) read: 10
+	"
+	^InterpretedWriteStream on: self type: type cacheSize: size
+! !
+
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+interpreting: writer size: byteSize
+	"Converts objects into bytes in a binary destination according to provided @writer block. The block is evaluated with an instance of InterpretedBytes an index and object to write into the bytes.
+	""	type		<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
+		byteSize	<Integer>	byte size of an element
+		^			<InterpretedWriteStream>
+	""
+		| points bytes |
+		points := Random new reading transforming: [ :in :out | out put: in get @ in get ].
+		bytes := (ByteArray new writing interpreting: [ :b :i :o | (b floatAt: i put: o x) @ (b floatAt: i + 4 put: o y) ] size: 8 )
+			write: 10 from: points;
+			close;
+			terminal.
+		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8 cacheSize: 5) read: 5
+	"
+	^InterpretedWriteStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: writer cacheSize: 1
+! !
+
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+interpreting: writer size: byteSize cacheSize: cacheSize
+	"Converts objects into bytes in a binary destination according to provided @writer block. The block is evaluated with an instance of InterpretedBytes an index and object to write into the bytes.
+	""	type		<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
+		byteSize	<Integer>	byte size of an element
+		cacheSize	<Integer>	requested cache size (in number of elements)
+		^			<InterpretedWriteStream>
+	""
+		| points bytes |
+		points := Random new reading transforming: [ :in :out | out put: in get @ in get ].
+		bytes := (ByteArray new writing interpreting: [ :b :i :o | (b floatAt: i put: o x) @ (b floatAt: i + 4 put: o y) ] size: 8 )
+			write: 10 from: points;
+			close;
+			terminal.
+		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8 cacheSize: 5) read: 5
+	"
+	^InterpretedWriteStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: writer cacheSize: cacheSize
+! !
+
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+marshaling
+	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID.
+	A marshaling write stream encodes objects into a binary destination stream.
+	""	^			<ObjectWriteSteam>
+	""
+		| rectangle bytes |
+		rectangle := 5 @ 5 extent: 5 @ 5.
+		bytes := ByteArray new writing marshaling put: rectangle; conclusion.
+		bytes reading marshaling get
+	"
+	^ObjectWriteStream on: self
+! !
+
+!Xtreams::WriteStream methodsFor:'interpreting'!
+
+marshaling: aMarshaler
+	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID. Custom marshaling schemes can be derived by subclassing ObjectMarshaler. Custom schemes must declare their own (unique) version ID. This method allows to employ a cusomt marshaler instead of the default one (STST2.0).
+	A marshaling write stream encodes objects into a binary destination stream.
+	""	aMarshaler	<ObjectMarshaler>	implements custom marshaling format
+		^			<ObjectWriteSteam>
+	""
+		| rectangle bytes |
+		rectangle := 5 @ 5 extent: 5 @ 5.
+		bytes := (ByteArray new writing marshaling: ObjectMarshaler new) put: rectangle; conclusion.
+		bytes reading marshaling get
+	"
+	^ObjectWriteStream on: self marshaler: aMarshaler
+! !
+
+!Xtreams::WriteStream methodsFor:'private'!
+
+nextPut: anObject
+	"This is here for compatibility with the existing StreamEncoders so that they can be re-used with transformation streams for encoding."
+	self put: anObject.
+	^anObject
+! !
+
+!Xtreams::WriteStream methodsFor:'private'!
+
+nextPutAll: aCollection
+	"This is here for compatibility with the existing StreamEncoders so that they can be re-used with transformation streams for encoding."
+	self write: aCollection.
+	^aCollection
+! !
+
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 collecting: aBlock
@@ -357,6 +499,7 @@
 	"
 	^CollectWriteStream on: self block: aBlock
 ! !
+
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 depairing
@@ -368,6 +511,7 @@
 		out put: association key.
 		out put: association value]
 ! !
+
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 doing: aBlock
@@ -379,6 +523,7 @@
 	"
 	^self collecting: [:each | (aBlock value: each). each]
 ! !
+
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 duplicating: aWriteStream
@@ -394,6 +539,7 @@
 	"
 	^DuplicateWriteStream on: self duplicate: aWriteStream
 ! !
+
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 encoding: anEncoding
@@ -411,6 +557,7 @@
 	"
 	^EncodeWriteStream on: self encoding: anEncoding
 ! !
+
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 encodingBase64
@@ -435,6 +582,7 @@
 		buffer: (RingBuffer on: (ByteArray new: 3));
 		yourself
 ! !
+
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 encodingHex
@@ -450,6 +598,7 @@
 		contentsSpecies: ByteString;
 		yourself
 ! !
+
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 injecting: initialObject into: aBlock
@@ -464,107 +613,7 @@
 	nextObject := initialObject.
 	^self collecting: [:each | nextObject := aBlock cull: nextObject cull: each]
 ! !
-!Xtreams::WriteStream methodsFor:'interpreting'!
 
-interpreting: type
-	"Converts consumed elements into bytes of pre-configured (primitive) CType, e.g. float, long etc. The type of the written elements must match the CType and the underlying destination must be binary.
-	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
-		^		<InterpretedWriteStream>
-	""
-		| doubles bytes |
-		doubles := [ Random new next ] reading.
-		bytes := (ByteArray new writing interpreting: #double)
-			write: 10 from: doubles;
-			close;
-			terminal.
-		(bytes reading interpreting: #double) read: 10
-	"
-	^self interpreting: type cacheSize: 1
-! !
-!Xtreams::WriteStream methodsFor:'interpreting'!
-
-interpreting: type cacheSize: size
-	"Converts consumed elements into bytes of pre-configured (primitive) CType, e.g. float, long etc. The type of the written elements must match the CType and the underlying destination must be binary.
-	""	type	<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
-		size		<Integer>	requested buffer size (in number of elements)
-		^		<InterpretedWriteStream>
-	""
-		| doubles bytes |
-		doubles := [ Random new next ] reading.
-		bytes := (ByteArray new writing interpreting: #double size: 10)
-			write: 10 from: doubles;
-			close;
-			terminal.
-		(bytes reading interpreting: #double) read: 10
-	"
-	^InterpretedWriteStream on: self type: type cacheSize: size
-! !
-!Xtreams::WriteStream methodsFor:'interpreting'!
-
-interpreting: writer size: byteSize
-	"Converts objects into bytes in a binary destination according to provided @writer block. The block is evaluated with an instance of InterpretedBytes an index and object to write into the bytes.
-	""	type		<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
-		byteSize	<Integer>	byte size of an element
-		^			<InterpretedWriteStream>
-	""
-		| points bytes |
-		points := Random new reading transforming: [ :in :out | out put: in get @ in get ].
-		bytes := (ByteArray new writing interpreting: [ :b :i :o | (b floatAt: i put: o x) @ (b floatAt: i + 4 put: o y) ] size: 8 )
-			write: 10 from: points;
-			close;
-			terminal.
-		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8 cacheSize: 5) read: 5
-	"
-	^InterpretedWriteStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: writer cacheSize: 1
-! !
-!Xtreams::WriteStream methodsFor:'interpreting'!
-
-interpreting: writer size: byteSize cacheSize: cacheSize
-	"Converts objects into bytes in a binary destination according to provided @writer block. The block is evaluated with an instance of InterpretedBytes an index and object to write into the bytes.
-	""	type		<Symbol>	identifies a (primitive) CType, e.g. #float, #long (mapped via Interpretations)
-		byteSize	<Integer>	byte size of an element
-		cacheSize	<Integer>	requested cache size (in number of elements)
-		^			<InterpretedWriteStream>
-	""
-		| points bytes |
-		points := Random new reading transforming: [ :in :out | out put: in get @ in get ].
-		bytes := (ByteArray new writing interpreting: [ :b :i :o | (b floatAt: i put: o x) @ (b floatAt: i + 4 put: o y) ] size: 8 )
-			write: 10 from: points;
-			close;
-			terminal.
-		(bytes reading interpreting: [ :b :i | (b floatAt: i) @ (b floatAt: i + 4) ] size: 8 cacheSize: 5) read: 5
-	"
-	^InterpretedWriteStream on: self bytesPerElement: byteSize contentsSpecies: Array operation: writer cacheSize: cacheSize
-! !
-!Xtreams::WriteStream methodsFor:'interpreting'!
-
-marshaling
-	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID.
-	A marshaling write stream encodes objects into a binary destination stream.
-	""	^			<ObjectWriteSteam>
-	""
-		| rectangle bytes |
-		rectangle := 5 @ 5 extent: 5 @ 5.
-		bytes := ByteArray new writing marshaling put: rectangle; conclusion.
-		bytes reading marshaling get
-	"
-	^ObjectWriteStream on: self
-! !
-!Xtreams::WriteStream methodsFor:'interpreting'!
-
-marshaling: aMarshaler
-	"Marshaling streams are used to encode arbitrary smalltalk objects into a sequence of bytes suitable for binary storage or transport. The format of the binary encoding is defined by an ObjectMarshaler and is identified by particular version ID. Custom marshaling schemes can be derived by subclassing ObjectMarshaler. Custom schemes must declare their own (unique) version ID. This method allows to employ a cusomt marshaler instead of the default one (STST2.0).
-	A marshaling write stream encodes objects into a binary destination stream.
-	""	aMarshaler	<ObjectMarshaler>	implements custom marshaling format
-		^			<ObjectWriteSteam>
-	""
-		| rectangle bytes |
-		rectangle := 5 @ 5 extent: 5 @ 5.
-		bytes := (ByteArray new writing marshaling: ObjectMarshaler new) put: rectangle; conclusion.
-		bytes reading marshaling get
-	"
-	^ObjectWriteStream on: self marshaler: aMarshaler
-! !
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 monitoring: aNotificationBlock every: aNotificationInterval
@@ -601,20 +650,7 @@
 	timer := Timer every: aNotificationInterval resume: notifyProcess.
 	^monitoring
 ! !
-!Xtreams::WriteStream methodsFor:'private'!
 
-nextPut: anObject
-	"This is here for compatibility with the existing StreamEncoders so that they can be re-used with transformation streams for encoding."
-	self put: anObject.
-	^anObject
-! !
-!Xtreams::WriteStream methodsFor:'private'!
-
-nextPutAll: aCollection
-	"This is here for compatibility with the existing StreamEncoders so that they can be re-used with transformation streams for encoding."
-	self write: aCollection.
-	^aCollection
-! !
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 pairing
@@ -622,6 +658,7 @@
 
 	^self transforming: [:in :out | out put: (Association key: in get value: in get)]
 ! !
+
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 rejecting: aBlock
@@ -633,6 +670,7 @@
 	"
 	^self selecting: [:each | (aBlock cull: each) not]
 ! !
+
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 selecting: aBlock
@@ -648,6 +686,7 @@
 		aBlock cull: value] whileFalse.
 		output put: value]
 ! !
+
 !Xtreams::WriteStream methodsFor:'transforming'!
 
 transforming: aBlock
@@ -675,8 +714,4 @@
 	"
 	^TransformWriteStream on: self block: aBlock
 ! !
-!stx_goodies_xtreams_transforms class methodsFor:'documentation'!
 
-extensionsVersion_SVN
-    ^ '$Id$'
-! !
--- a/transforms/stx_goodies_xtreams_transforms.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/stx_goodies_xtreams_transforms.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,5 +1,9 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:10:37 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms' }"
 
+"{ NameSpace: Xtreams }"
+
 LibraryDefinition subclass:#stx_goodies_xtreams_transforms
 	instanceVariableNames:''
 	classVariableNames:''
--- a/transforms/tests/Xtreams__DuplicateTest.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/tests/Xtreams__DuplicateTest.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:11:28 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms/tests' }"
 
 "{ NameSpace: Xtreams }"
--- a/transforms/tests/Xtreams__InterpretingStreamTest.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/tests/Xtreams__InterpretingStreamTest.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:11:28 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms/tests' }"
 
 "{ NameSpace: Xtreams }"
--- a/transforms/tests/Xtreams__MessagePackMarshalerTest.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/tests/Xtreams__MessagePackMarshalerTest.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:11:28 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms/tests' }"
 
 "{ NameSpace: Xtreams }"
--- a/transforms/tests/Xtreams__ObjectMarshalerTest.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/tests/Xtreams__ObjectMarshalerTest.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:11:28 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms/tests' }"
 
 "{ NameSpace: Xtreams }"
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/transforms/tests/extensions.sav	Sun Jan 15 02:18:53 2012 +0000
@@ -0,0 +1,432 @@
+"{ Package: 'stx:goodies/xtreams/transforms/tests' }"
+
+!
+
+!Xtreams::CollectionReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadRejecting
+        self output write: #[ 1 2 3 4 5 6 7 8 9 ].
+        self assert: ((self input rejecting: [ :e | e even ]) read: 5) = #[ 1 3 5 7 9 ]
+! !
+!Xtreams::CollectionReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadSelecting
+        self output write: #[ 1 2 3 4 5 6 7 8 9 ].
+        self assert: ((self input selecting: [ :e | e even ]) read: 4) = #[ 2 4 6 8 ]
+! !
+!Xtreams::CollectionReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteRejecting
+        (self output rejecting: [ :e | e even ] ) write: #[ 1 2 3 4 5 6 7 8 9 ]; close.
+        self assert: (self input read: 5) = #[ 1 3 5 7 9 ]
+! !
+!Xtreams::CollectionReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteSelecting
+        (self output selecting: [ :e | e even]) write: #[ 1 2 3 4 5 6 7 8 9 ]; close.
+        self assert: (self input read: 4) = #[ 2 4 6 8 ]
+! !
+!Xtreams::CollectionReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteTransformHexToByte
+	| hex2Byte decoder result |
+	decoder := [ :char | ('0123456789ABCDEF' indexOf: char asUppercase) - 1 ].
+	hex2Byte := 
+		self output transforming: [ :in :out |
+			out put: (((decoder value: in get) bitShift: 4) + (decoder value: in get)) ].
+	hex2Byte buffer: (ElasticBuffer on: (ByteString new: 16)).
+	hex2Byte write: 'ab'.
+	hex2Byte write: 'cdef'.
+	hex2Byte close.
+	self assert: self input get = 16rAB.
+	result := self input read: 2.
+	self assert: result = #[16rcd 16ref].
+! !
+!Xtreams::FiniteReadingWritingTests methodsFor:'tests - interpreting'!
+
+testInterpretingDoubles
+	| doubles result |
+	doubles := (1 to: 10) reading collect: [ :i | i reciprocal asDouble ].
+	(self output interpreting: #double) write: doubles; close.
+	result := (self input interpreting: #double) rest.
+	self assert: result = doubles
+! !
+!Xtreams::FiniteReadingWritingTests methodsFor:'tests - transforming'!
+
+testWriteTransformingOverLimitingPastEnd
+
+	| limited transferred |
+	limited := (self output limiting: 10) transforming: [ :in :out | out put: in get ].
+	self assert: (
+		[	limited write: (ByteArray withAll: (1 to: 20)).
+			false
+		] on: Incomplete do: [ :ex | ex count = 11 ] ).
+	transferred := self input read: 10.
+	self assert: transferred = (ByteArray withAll: (1 to: 10))
+! !
+!Xtreams::FiniteReadingWritingTests methodsFor:'tests - transforming'!
+
+testWriteTransformingPastEnd
+	| count transformed |
+	count := 1.
+	transformed := self output transforming: [:in :out |
+		count = 2 ifTrue: [Incomplete zero raise].
+		out put: in get.
+		count := count + 1].
+	self assert: (
+		[	transformed write: #[ 1 2 3 ].
+			false
+		] on: Incomplete do: [ :ex | ex count = 1 ]).
+	transformed close.
+	self assert: self input get = 1.
+	self should: [self input get] raise: Incomplete.
+	self should: [self input get] raise: Incomplete
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testDoing
+	| outing inning |
+	outing := ByteArray new writing.
+	(self output doing: [:each | outing put: each]) write: #[ 1 2 3 4 5 ].
+	self assert: outing contents = #[ 1 2 3 4 5 ].
+
+	inning := ByteArray new writing.
+	self assert: ((self input doing: [:each | inning put: each]) read: 5) = #[ 1 2 3 4 5 ].
+	self assert: inning contents = #[ 1 2 3 4 5 ]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
+
+testInterpretingPoints
+
+	| points result |
+	points := (Random new reading transforming: [ :in :out | out put: in get @ in get ]) read: 5.
+	(self output interpreting: [ :b :i :o | b doubleAt: i put: o x. b doubleAt: i + 8 put: o y ] size: 16 )
+		write: points;
+		close.
+	result := (self input interpreting: [ :b :i | (b doubleAt: i) @ (b doubleAt: i + 8) ] size: 16 cacheSize: 5) read: points size.
+	self assert: points = result
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
+
+testMarshaling
+	| object result in out |
+	object := Object new.
+	out := self output marshaling.
+	in := self input marshaling.
+	2 timesRepeat: 
+		[out put: ((1 to: 11) collect: [:each | (1 to: 11) collect: [:ea | object]]).
+		result := in get.
+		self assert: result size = 11.
+		self assert: (result allSatisfy: [:each | each allSatisfy: [:ea | ea == result first first]])]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadCollecting
+	| data |
+	data := #[ 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 ].
+	self output write: data.
+	self assert: ((self input collecting: [:e | e * e]) read: data size) = (ByteArray withAll: (data collect: [:e | e * e]))
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadCollectingContentsSpeciesChanged
+	| data result |
+	data := ByteArray withAll: ((1 to: 16) collect: [:index | 65]).
+	self output write: data.
+	result :=
+		(self input collecting: [:e | Character codePoint: e])
+			contentsSpecies: String;
+			read: data size.
+	self assert: result = (String withAll: (data asArray collect: [:e | Character codePoint: e]))
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
+
+testReadDecodingBase64
+	(self output encoding: #ascii)
+		write: 
+'TWFuIGlzIGRpc3Rpbmd1aXNoZWQsIG5vdCBvbmx5IGJ5IGhpcyByZWFzb24sIGJ1dCBieSB0aGlz
+IHNpbmd1bGFyIHBhc3Npb24gZnJvbSBvdGhlciBhbmltYWxzLCB3aGljaCBpcyBhIGx1c3Qgb2Yg
+dGhlIG1pbmQsIHRoYXQgYnkgYSBwZXJzZXZlcmFuY2Ugb2YgZGVsaWdodCBpbiB0aGUgY29udGlu
+dWVkIGFuZCBpbmRlZmF0aWdhYmxlIGdlbmVyYXRpb24gb2Yga25vd2xlZGdlLCBleGNlZWRzIHRo
+ZSBzaG9ydCB2ZWhlbWVuY2Ugb2YgYW55IGNhcm5hbCBwbGVhc3VyZS4=';
+		close.
+	self assert: (((self input encoding: #ascii) encodingBase64 encoding: #ascii) read: 269) = 'Man is distinguished, not only by his reason, but by this singular passion from other animals, which is a lust of the mind, that by a perseverance of delight in the continued and indefatigable generation of knowledge, exceeds the short vehemence of any carnal pleasure.'
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
+
+testReadDecodingCRLF
+
+	| result |
+	self output write: #[104 101 108 108 111 13 10 119 111 114 108 100 10 13 13 10 10 ]; close.
+	result := (self input encoding: #ascii) read: 15.
+	self assert: result = 'hello\world\\\\' withCRs
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
+
+testReadDecodingTransparent
+
+	| result bytes |
+	bytes := #[104 101 108 108 111 13 10 119 111 114 108 100 13 10 13 10 13 10 ].
+	self output write: bytes; close.
+	result := (self input encoding: #ascii) setLineEndTransparent read: bytes size.
+	self assert: result = (String withAll: (bytes asArray collect: #asCharacter))
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
+
+testReadDecodingUTF16
+
+	| result bytes |
+	bytes := #[0 72 0 101 0 108 0 108 0 111 0 32 0 87 0 111 0 114 0 108 0 100 0 33].
+	self output write: bytes; close.
+	result := (self input encoding: #utf16) read: 12.
+	self assert: result = 'Hello World!!'
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
+
+testReadDecodingUTF8
+
+	| result bytes text |
+	text := 'Příliš žluťoučký kůň úpěl ďábelské ódy'.
+	bytes := #[80 197 153 195 173 108 105 197 161 32 197 190 108 117 197 165 111 117 196 141 107 195 189 32 107 197 175 197 136 32 195 186 112 196 155 108 32 196 143 195 161 98 101 108 115 107 195 169 32 195 179 100 121].
+	self output write: bytes; close.
+	result := (self input encoding: #utf8) read: text size.
+	self assert: result = text
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadDuplicating
+
+	| copy contents |
+	contents := Array withAll: (0 to: 15).
+	copy := Array new writing.
+	self assert: (contents reading duplicating: copy) rest = contents.
+	self assert: copy conclusion = contents
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadInjecting
+	self output write: #[ 1 2 3 4 ].
+	self assert: ((self input injecting: 0 into: [:all :each | all + each]) read: 4) = #[ 1 3 6 10 ]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadRejecting
+	self output write: #[ 1 2 3 4 5 6 7 8 9 ].
+	self assert: ((self input rejecting: #even) read: 5) = #[ 1 3 5 7 9 ]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadSelecting
+	self output write: #[ 1 2 3 4 5 6 7 8 9 ].
+	self assert: ((self input selecting: #even) read: 4) = #[ 2 4 6 8 ]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadTransforming1into2
+	| result |
+	self output write: #[ 1 2 3 ].
+	result :=
+		(self input transforming: [:in :out | | x | x := in get. out put: x; put: x])
+			read: 6.
+	self assert: result = #[ 1 1 2 2 3 3 ]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadTransforming2into1
+	| result |
+	self output write: #[ 1 2 3 4 ].
+	result :=
+		(self input transforming: [:in :out | in get. out put: in get])
+			read: 2.
+	self assert: result = #[ 2 4 ]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadTransformingPastEnd
+	| count transformed |
+	count := 1.
+	self output write: #[ 1 2 3 ]; close.
+	transformed := self input transforming: [:in :out |
+		count = 2 ifTrue: [Incomplete zero raise].
+		out put: in get.
+		count := count + 1].
+	self assert: transformed get = 1.
+	self should: [transformed get] raise: Incomplete.
+	self should: [transformed get] raise: Incomplete
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
+
+testReadUnsignedShortEndianness
+
+	self output write: #[ 16rFF 16r00 16rFF 00]; close.
+	self assert: (self input interpreting: #unsignedShort_le) get = 16rFF.
+	self assert: (self input interpreting: #unsignedShort_be) get = 16rFF00.
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteCollecting
+	| data |
+	data := 1 to: 15.
+	(self output collecting: [:e | e * e]) write: data.
+	self assert: (self input read: data size) = (ByteArray withAll: (data collect: [:e | e * e]))
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteCollectingIncompatibleContentSpecies
+	| data |
+	data := (1 to: 15) collect: [ :x | x @ 0 ].
+	(self output collecting: [:e | e x ]) write: data.
+	self assert: (self input read: data size) = (ByteArray withAll: (data collect: [:e | e x]))
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteCollectingMultipleBufferSize
+	| data |
+	data := (1 to: DefaultBufferSize + 500) collect: [ :i | i \\ 16 ].
+	self timeout: 1 seconds
+		server:
+			[(self output collecting: [:e | e * e])
+				write: data;
+				close.
+			true]
+		client: [(self input read: data size) = (ByteArray withAll: (data collect: [:e | e * e]))]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteDuplicating
+
+	| original copy contents |
+	contents := Array withAll: (0 to: 15).
+	original := Array new writing.
+	copy := Array new writing.
+	(original duplicating: copy) write: contents.
+	self assert: original conclusion = contents.
+	self assert: copy conclusion = contents
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
+
+testWriteEncodingBase64
+	((self output encoding: #ascii) encodingBase64 encoding: #ascii)
+		write: 'Man is distinguished, not only by his reason, but by this singular passion from other animals, which is a lust of the mind, that by a perseverance of delight in the continued and indefatigable generation of knowledge, exceeds the short vehemence of any carnal pleasure.';
+		close.
+	self assert: ((self input encoding: #ascii) read: 360) = 'TWFuIGlzIGRpc3Rpbmd1aXNoZWQsIG5vdCBvbmx5IGJ5IGhpcyByZWFzb24sIGJ1dCBieSB0aGlzIHNpbmd1bGFyIHBhc3Npb24gZnJvbSBvdGhlciBhbmltYWxzLCB3aGljaCBpcyBhIGx1c3Qgb2YgdGhlIG1pbmQsIHRoYXQgYnkgYSBwZXJzZXZlcmFuY2Ugb2YgZGVsaWdodCBpbiB0aGUgY29udGludWVkIGFuZCBpbmRlZmF0aWdhYmxlIGdlbmVyYXRpb24gb2Yga25vd2xlZGdlLCBleGNlZWRzIHRoZSBzaG9ydCB2ZWhlbWVuY2Ugb2YgYW55IGNhcm5hbCBwbGVhc3VyZS4='
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
+
+testWriteEncodingCRLF
+
+	| result isCRLF |
+	(self output encoding: #ascii)
+		write: 'hello\world\\\' withCRs;
+		close.
+	isCRLF := IOAccessor defaultClass = PCIOAccessor.
+	result := self input read: (isCRLF ifTrue: [18] ifFalse: [14]).
+	
+	self assert: result = (isCRLF
+		ifTrue: [#[104 101 108 108 111 13 10 119 111 114 108 100 13 10 13 10 13 10 ] ]
+		ifFalse: [#[104 101 108 108 111 10 119 111 114 108 100 10 10 10 ] ])
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
+
+testWriteEncodingTransparent
+
+	| data result bytes |
+	bytes := #[104 101 108 108 111 13 10 119 111 114 108 100 13 10 13 10 13 10 ].
+	data := String withAll: (bytes asArray collect: #asCharacter).
+	(self output encoding: #ascii)
+		setLineEndTransparent;
+		write: data;
+		close.
+	result := self input read: data size.
+	self assert: result = bytes
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
+
+testWriteEncodingUTF16
+
+	| result bytes |
+	bytes := #[0 72 0 101 0 108 0 108 0 111 0 32 0 87 0 111 0 114 0 108 0 100 0 33].
+	(self output encoding: #utf16) write: 'Hello World!!'; close.
+	result := self input read: 24.
+	self assert: result = bytes
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
+
+testWriteEncodingUTF8
+
+	| result bytes text |
+	text := 'Příliš žluťoučký kůň úpěl ďábelské ódy'.
+	bytes := #[80 197 153 195 173 108 105 197 161 32 197 190 108 117 197 165 111 117 196 141 107 195 189 32 107 197 175 197 136 32 195 186 112 196 155 108 32 196 143 195 161 98 101 108 115 107 195 169 32 195 179 100 121].
+	(self output encoding: #utf8) write: text; close.
+	result := self input read: bytes size.
+	self assert: result = bytes
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteInjecting
+	(self output injecting: 0 into: [:all :each | all + each])
+		write: #[ 1 2 3 4 ]; close.
+	self assert: (self input read: 4) = #[ 1 3 6 10 ]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteRejecting
+	(self output rejecting: #even) write: #[ 1 2 3 4 5 6 7 8 9 ]; close.
+	self assert: (self input read: 5) = #[ 1 3 5 7 9 ]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteSelecting
+	(self output selecting: #even) write: #[ 1 2 3 4 5 6 7 8 9 ]; close.
+	self assert: (self input read: 4) = #[ 2 4 6 8 ]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteTransformHexToByte
+	| hex2Byte decoder result |
+	decoder := [ :char | ('0123456789ABCDEF' indexOf: char asUppercase) - 1 ].
+	hex2Byte := 
+		self output transforming: [ :in :out |
+			out put: (((decoder value: in get) bitShift: 4) + (decoder value: in get)) ].
+	hex2Byte buffer: (ElasticBuffer on: (ByteString new: 16)).
+	hex2Byte write: 'ab'.
+	self assert: self input get = 16rAB.
+	hex2Byte write: 'cdef'.
+	hex2Byte close.
+	result := self input read: 2.
+	self assert: result = #[16rcd 16ref].
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteTransforming1into2
+	| result |
+	(self output transforming: [:in :out | | x | x := in get. out put: x; put: x])
+		write: #[ 1 2 3 ];
+		close.
+	result := (self input read: 6).
+	self assert: result = #[ 1 1 2 2 3 3 ]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteTransforming2into1
+	| result |
+	(self output transforming: [:in :out | in get. out put: in get])
+		write: #[ 1 2 3 4 ];
+		close.
+	result := self input read: 2.
+	self assert: result = #[ 2 4 ]
+! !
+!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
+
+testWriteUnsignedShortEndianness
+
+	(self output interpreting: #unsignedShort_le) put: 16rFF.
+	(self output interpreting: #unsignedShort_be) put: 16rFF00.
+	self output close.
+	self assert: (self input read: 4) = #[ 16rFF 16r00 16rFF 00]
+! !
+!stx_goodies_xtreams_transforms_tests class methodsFor:'documentation'!
+
+extensionsVersion_SVN
+    ^ '$Id: extensions.st 20 2011-11-21 06:04:22Z mkobetic $'
+! !
--- a/transforms/tests/extensions.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/tests/extensions.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,6 +1,5 @@
-"{ Package: 'stx:goodies/xtreams/transforms/tests' }"
-
-!
+"{ Encoding: utf8 }" !
+"{ Package: 'stx:goodies/xtreams/transforms/tests' }" !
 
 !Xtreams::CollectionReadingWritingTest methodsFor:'tests - transforming'!
 
@@ -8,24 +7,28 @@
         self output write: #[ 1 2 3 4 5 6 7 8 9 ].
         self assert: ((self input rejecting: [ :e | e even ]) read: 5) = #[ 1 3 5 7 9 ]
 ! !
+
 !Xtreams::CollectionReadingWritingTest methodsFor:'tests - transforming'!
 
 testReadSelecting
         self output write: #[ 1 2 3 4 5 6 7 8 9 ].
         self assert: ((self input selecting: [ :e | e even ]) read: 4) = #[ 2 4 6 8 ]
 ! !
+
 !Xtreams::CollectionReadingWritingTest methodsFor:'tests - transforming'!
 
 testWriteRejecting
         (self output rejecting: [ :e | e even ] ) write: #[ 1 2 3 4 5 6 7 8 9 ]; close.
         self assert: (self input read: 5) = #[ 1 3 5 7 9 ]
 ! !
+
 !Xtreams::CollectionReadingWritingTest methodsFor:'tests - transforming'!
 
 testWriteSelecting
         (self output selecting: [ :e | e even]) write: #[ 1 2 3 4 5 6 7 8 9 ]; close.
         self assert: (self input read: 4) = #[ 2 4 6 8 ]
 ! !
+
 !Xtreams::CollectionReadingWritingTest methodsFor:'tests - transforming'!
 
 testWriteTransformHexToByte
@@ -42,6 +45,7 @@
 	result := self input read: 2.
 	self assert: result = #[16rcd 16ref].
 ! !
+
 !Xtreams::FiniteReadingWritingTests methodsFor:'tests - interpreting'!
 
 testInterpretingDoubles
@@ -51,6 +55,7 @@
 	result := (self input interpreting: #double) rest.
 	self assert: result = doubles
 ! !
+
 !Xtreams::FiniteReadingWritingTests methodsFor:'tests - transforming'!
 
 testWriteTransformingOverLimitingPastEnd
@@ -64,6 +69,7 @@
 	transferred := self input read: 10.
 	self assert: transferred = (ByteArray withAll: (1 to: 10))
 ! !
+
 !Xtreams::FiniteReadingWritingTests methodsFor:'tests - transforming'!
 
 testWriteTransformingPastEnd
@@ -82,63 +88,7 @@
 	self should: [self input get] raise: Incomplete.
 	self should: [self input get] raise: Incomplete
 ! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
 
-testDoing
-	| outing inning |
-	outing := ByteArray new writing.
-	(self output doing: [:each | outing put: each]) write: #[ 1 2 3 4 5 ].
-	self assert: outing contents = #[ 1 2 3 4 5 ].
-
-	inning := ByteArray new writing.
-	self assert: ((self input doing: [:each | inning put: each]) read: 5) = #[ 1 2 3 4 5 ].
-	self assert: inning contents = #[ 1 2 3 4 5 ]
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
-
-testInterpretingPoints
-
-	| points result |
-	points := (Random new reading transforming: [ :in :out | out put: in get @ in get ]) read: 5.
-	(self output interpreting: [ :b :i :o | b doubleAt: i put: o x. b doubleAt: i + 8 put: o y ] size: 16 )
-		write: points;
-		close.
-	result := (self input interpreting: [ :b :i | (b doubleAt: i) @ (b doubleAt: i + 8) ] size: 16 cacheSize: 5) read: points size.
-	self assert: points = result
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
-
-testMarshaling
-	| object result in out |
-	object := Object new.
-	out := self output marshaling.
-	in := self input marshaling.
-	2 timesRepeat: 
-		[out put: ((1 to: 11) collect: [:each | (1 to: 11) collect: [:ea | object]]).
-		result := in get.
-		self assert: result size = 11.
-		self assert: (result allSatisfy: [:each | each allSatisfy: [:ea | ea == result first first]])]
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testReadCollecting
-	| data |
-	data := #[ 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 ].
-	self output write: data.
-	self assert: ((self input collecting: [:e | e * e]) read: data size) = (ByteArray withAll: (data collect: [:e | e * e]))
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testReadCollectingContentsSpeciesChanged
-	| data result |
-	data := ByteArray withAll: ((1 to: 16) collect: [:index | 65]).
-	self output write: data.
-	result :=
-		(self input collecting: [:e | Character codePoint: e])
-			contentsSpecies: String;
-			read: data size.
-	self assert: result = (String withAll: (data asArray collect: [:e | Character codePoint: e]))
-! !
 !Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
 
 testReadDecodingBase64
@@ -152,6 +102,7 @@
 		close.
 	self assert: (((self input encoding: #ascii) encodingBase64 encoding: #ascii) read: 269) = 'Man is distinguished, not only by his reason, but by this singular passion from other animals, which is a lust of the mind, that by a perseverance of delight in the continued and indefatigable generation of knowledge, exceeds the short vehemence of any carnal pleasure.'
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
 
 testReadDecodingCRLF
@@ -161,6 +112,7 @@
 	result := (self input encoding: #ascii) read: 15.
 	self assert: result = 'hello\world\\\\' withCRs
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
 
 testReadDecodingTransparent
@@ -171,6 +123,7 @@
 	result := (self input encoding: #ascii) setLineEndTransparent read: bytes size.
 	self assert: result = (String withAll: (bytes asArray collect: #asCharacter))
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
 
 testReadDecodingUTF16
@@ -181,128 +134,19 @@
 	result := (self input encoding: #utf16) read: 12.
 	self assert: result = 'Hello World!!'
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
 
 testReadDecodingUTF8
 
 	| result bytes text |
-	text := 'Příliš žluťoučký kůň úpěl ďábelské ódy'.
+	text := 'Příliš žluťoučký kůň úpěl ďábelské ódy'.
 	bytes := #[80 197 153 195 173 108 105 197 161 32 197 190 108 117 197 165 111 117 196 141 107 195 189 32 107 197 175 197 136 32 195 186 112 196 155 108 32 196 143 195 161 98 101 108 115 107 195 169 32 195 179 100 121].
 	self output write: bytes; close.
 	result := (self input encoding: #utf8) read: text size.
 	self assert: result = text
 ! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
 
-testReadDuplicating
-
-	| copy contents |
-	contents := Array withAll: (0 to: 15).
-	copy := Array new writing.
-	self assert: (contents reading duplicating: copy) rest = contents.
-	self assert: copy conclusion = contents
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testReadInjecting
-	self output write: #[ 1 2 3 4 ].
-	self assert: ((self input injecting: 0 into: [:all :each | all + each]) read: 4) = #[ 1 3 6 10 ]
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testReadRejecting
-	self output write: #[ 1 2 3 4 5 6 7 8 9 ].
-	self assert: ((self input rejecting: #even) read: 5) = #[ 1 3 5 7 9 ]
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testReadSelecting
-	self output write: #[ 1 2 3 4 5 6 7 8 9 ].
-	self assert: ((self input selecting: #even) read: 4) = #[ 2 4 6 8 ]
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testReadTransforming1into2
-	| result |
-	self output write: #[ 1 2 3 ].
-	result :=
-		(self input transforming: [:in :out | | x | x := in get. out put: x; put: x])
-			read: 6.
-	self assert: result = #[ 1 1 2 2 3 3 ]
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testReadTransforming2into1
-	| result |
-	self output write: #[ 1 2 3 4 ].
-	result :=
-		(self input transforming: [:in :out | in get. out put: in get])
-			read: 2.
-	self assert: result = #[ 2 4 ]
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testReadTransformingPastEnd
-	| count transformed |
-	count := 1.
-	self output write: #[ 1 2 3 ]; close.
-	transformed := self input transforming: [:in :out |
-		count = 2 ifTrue: [Incomplete zero raise].
-		out put: in get.
-		count := count + 1].
-	self assert: transformed get = 1.
-	self should: [transformed get] raise: Incomplete.
-	self should: [transformed get] raise: Incomplete
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
-
-testReadUnsignedShortEndianness
-
-	self output write: #[ 16rFF 16r00 16rFF 00]; close.
-	self assert: (self input interpreting: #unsignedShort_le) get = 16rFF.
-	self assert: (self input interpreting: #unsignedShort_be) get = 16rFF00.
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testWriteCollecting
-	| data |
-	data := 1 to: 15.
-	(self output collecting: [:e | e * e]) write: data.
-	self assert: (self input read: data size) = (ByteArray withAll: (data collect: [:e | e * e]))
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testWriteCollectingIncompatibleContentSpecies
-	| data |
-	data := (1 to: 15) collect: [ :x | x @ 0 ].
-	(self output collecting: [:e | e x ]) write: data.
-	self assert: (self input read: data size) = (ByteArray withAll: (data collect: [:e | e x]))
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testWriteCollectingMultipleBufferSize
-	| data |
-	data := (1 to: DefaultBufferSize + 500) collect: [ :i | i \\ 16 ].
-	self timeout: 1 seconds
-		server:
-			[(self output collecting: [:e | e * e])
-				write: data;
-				close.
-			true]
-		client: [(self input read: data size) = (ByteArray withAll: (data collect: [:e | e * e]))]
-! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
-
-testWriteDuplicating
-
-	| original copy contents |
-	contents := Array withAll: (0 to: 15).
-	original := Array new writing.
-	copy := Array new writing.
-	(original duplicating: copy) write: contents.
-	self assert: original conclusion = contents.
-	self assert: copy conclusion = contents
-! !
 !Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
 
 testWriteEncodingBase64
@@ -311,6 +155,7 @@
 		close.
 	self assert: ((self input encoding: #ascii) read: 360) = 'TWFuIGlzIGRpc3Rpbmd1aXNoZWQsIG5vdCBvbmx5IGJ5IGhpcyByZWFzb24sIGJ1dCBieSB0aGlzIHNpbmd1bGFyIHBhc3Npb24gZnJvbSBvdGhlciBhbmltYWxzLCB3aGljaCBpcyBhIGx1c3Qgb2YgdGhlIG1pbmQsIHRoYXQgYnkgYSBwZXJzZXZlcmFuY2Ugb2YgZGVsaWdodCBpbiB0aGUgY29udGludWVkIGFuZCBpbmRlZmF0aWdhYmxlIGdlbmVyYXRpb24gb2Yga25vd2xlZGdlLCBleGNlZWRzIHRoZSBzaG9ydCB2ZWhlbWVuY2Ugb2YgYW55IGNhcm5hbCBwbGVhc3VyZS4='
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
 
 testWriteEncodingCRLF
@@ -326,6 +171,7 @@
 		ifTrue: [#[104 101 108 108 111 13 10 119 111 114 108 100 13 10 13 10 13 10 ] ]
 		ifFalse: [#[104 101 108 108 111 10 119 111 114 108 100 10 10 10 ] ])
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
 
 testWriteEncodingTransparent
@@ -340,6 +186,7 @@
 	result := self input read: data size.
 	self assert: result = bytes
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
 
 testWriteEncodingUTF16
@@ -350,17 +197,214 @@
 	result := self input read: 24.
 	self assert: result = bytes
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - encoding'!
 
 testWriteEncodingUTF8
 
 	| result bytes text |
-	text := 'Příliš žluťoučký kůň úpěl ďábelské ódy'.
+	text := 'Příliš žluťoučký kůň úpěl ďábelské ódy'.
 	bytes := #[80 197 153 195 173 108 105 197 161 32 197 190 108 117 197 165 111 117 196 141 107 195 189 32 107 197 175 197 136 32 195 186 112 196 155 108 32 196 143 195 161 98 101 108 115 107 195 169 32 195 179 100 121].
 	(self output encoding: #utf8) write: text; close.
 	result := self input read: bytes size.
 	self assert: result = bytes
 ! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
+
+testInterpretingPoints
+
+	| points result |
+	points := (Random new reading transforming: [ :in :out | out put: in get @ in get ]) read: 5.
+	(self output interpreting: [ :b :i :o | b doubleAt: i put: o x. b doubleAt: i + 8 put: o y ] size: 16 )
+		write: points;
+		close.
+	result := (self input interpreting: [ :b :i | (b doubleAt: i) @ (b doubleAt: i + 8) ] size: 16 cacheSize: 5) read: points size.
+	self assert: points = result
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
+
+testMarshaling
+	| object result in out |
+	object := Object new.
+	out := self output marshaling.
+	in := self input marshaling.
+	2 timesRepeat: 
+		[out put: ((1 to: 11) collect: [:each | (1 to: 11) collect: [:ea | object]]).
+		result := in get.
+		self assert: result size = 11.
+		self assert: (result allSatisfy: [:each | each allSatisfy: [:ea | ea == result first first]])]
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
+
+testReadUnsignedShortEndianness
+
+	self output write: #[ 16rFF 16r00 16rFF 00]; close.
+	self assert: (self input interpreting: #unsignedShort_le) get = 16rFF.
+	self assert: (self input interpreting: #unsignedShort_be) get = 16rFF00.
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
+
+testWriteUnsignedShortEndianness
+
+	(self output interpreting: #unsignedShort_le) put: 16rFF.
+	(self output interpreting: #unsignedShort_be) put: 16rFF00.
+	self output close.
+	self assert: (self input read: 4) = #[ 16rFF 16r00 16rFF 00]
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testDoing
+	| outing inning |
+	outing := ByteArray new writing.
+	(self output doing: [:each | outing put: each]) write: #[ 1 2 3 4 5 ].
+	self assert: outing contents = #[ 1 2 3 4 5 ].
+
+	inning := ByteArray new writing.
+	self assert: ((self input doing: [:each | inning put: each]) read: 5) = #[ 1 2 3 4 5 ].
+	self assert: inning contents = #[ 1 2 3 4 5 ]
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadCollecting
+	| data |
+	data := #[ 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 ].
+	self output write: data.
+	self assert: ((self input collecting: [:e | e * e]) read: data size) = (ByteArray withAll: (data collect: [:e | e * e]))
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadCollectingContentsSpeciesChanged
+	| data result |
+	data := ByteArray withAll: ((1 to: 16) collect: [:index | 65]).
+	self output write: data.
+	result :=
+		(self input collecting: [:e | Character codePoint: e])
+			contentsSpecies: String;
+			read: data size.
+	self assert: result = (String withAll: (data asArray collect: [:e | Character codePoint: e]))
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadDuplicating
+
+	| copy contents |
+	contents := Array withAll: (0 to: 15).
+	copy := Array new writing.
+	self assert: (contents reading duplicating: copy) rest = contents.
+	self assert: copy conclusion = contents
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadInjecting
+	self output write: #[ 1 2 3 4 ].
+	self assert: ((self input injecting: 0 into: [:all :each | all + each]) read: 4) = #[ 1 3 6 10 ]
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadRejecting
+	self output write: #[ 1 2 3 4 5 6 7 8 9 ].
+	self assert: ((self input rejecting: #even) read: 5) = #[ 1 3 5 7 9 ]
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadSelecting
+	self output write: #[ 1 2 3 4 5 6 7 8 9 ].
+	self assert: ((self input selecting: #even) read: 4) = #[ 2 4 6 8 ]
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadTransforming1into2
+	| result |
+	self output write: #[ 1 2 3 ].
+	result :=
+		(self input transforming: [:in :out | | x | x := in get. out put: x; put: x])
+			read: 6.
+	self assert: result = #[ 1 1 2 2 3 3 ]
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadTransforming2into1
+	| result |
+	self output write: #[ 1 2 3 4 ].
+	result :=
+		(self input transforming: [:in :out | in get. out put: in get])
+			read: 2.
+	self assert: result = #[ 2 4 ]
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testReadTransformingPastEnd
+	| count transformed |
+	count := 1.
+	self output write: #[ 1 2 3 ]; close.
+	transformed := self input transforming: [:in :out |
+		count = 2 ifTrue: [Incomplete zero raise].
+		out put: in get.
+		count := count + 1].
+	self assert: transformed get = 1.
+	self should: [transformed get] raise: Incomplete.
+	self should: [transformed get] raise: Incomplete
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteCollecting
+	| data |
+	data := 1 to: 15.
+	(self output collecting: [:e | e * e]) write: data.
+	self assert: (self input read: data size) = (ByteArray withAll: (data collect: [:e | e * e]))
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteCollectingIncompatibleContentSpecies
+	| data |
+	data := (1 to: 15) collect: [ :x | x @ 0 ].
+	(self output collecting: [:e | e x ]) write: data.
+	self assert: (self input read: data size) = (ByteArray withAll: (data collect: [:e | e x]))
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteCollectingMultipleBufferSize
+	| data |
+	data := (1 to: DefaultBufferSize + 500) collect: [ :i | i \\ 16 ].
+	self timeout: 1 seconds
+		server:
+			[(self output collecting: [:e | e * e])
+				write: data;
+				close.
+			true]
+		client: [(self input read: data size) = (ByteArray withAll: (data collect: [:e | e * e]))]
+! !
+
+!Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
+
+testWriteDuplicating
+
+	| original copy contents |
+	contents := Array withAll: (0 to: 15).
+	original := Array new writing.
+	copy := Array new writing.
+	(original duplicating: copy) write: contents.
+	self assert: original conclusion = contents.
+	self assert: copy conclusion = contents
+! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
 
 testWriteInjecting
@@ -368,18 +412,21 @@
 		write: #[ 1 2 3 4 ]; close.
 	self assert: (self input read: 4) = #[ 1 3 6 10 ]
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
 
 testWriteRejecting
 	(self output rejecting: #even) write: #[ 1 2 3 4 5 6 7 8 9 ]; close.
 	self assert: (self input read: 5) = #[ 1 3 5 7 9 ]
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
 
 testWriteSelecting
 	(self output selecting: #even) write: #[ 1 2 3 4 5 6 7 8 9 ]; close.
 	self assert: (self input read: 4) = #[ 2 4 6 8 ]
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
 
 testWriteTransformHexToByte
@@ -396,6 +443,7 @@
 	result := self input read: 2.
 	self assert: result = #[16rcd 16ref].
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
 
 testWriteTransforming1into2
@@ -406,6 +454,7 @@
 	result := (self input read: 6).
 	self assert: result = #[ 1 1 2 2 3 3 ]
 ! !
+
 !Xtreams::ReadingWritingTest methodsFor:'tests - transforming'!
 
 testWriteTransforming2into1
@@ -416,17 +465,4 @@
 	result := self input read: 2.
 	self assert: result = #[ 2 4 ]
 ! !
-!Xtreams::ReadingWritingTest methodsFor:'tests - interpreting'!
 
-testWriteUnsignedShortEndianness
-
-	(self output interpreting: #unsignedShort_le) put: 16rFF.
-	(self output interpreting: #unsignedShort_be) put: 16rFF00.
-	self output close.
-	self assert: (self input read: 4) = #[ 16rFF 16r00 16rFF 00]
-! !
-!stx_goodies_xtreams_transforms_tests class methodsFor:'documentation'!
-
-extensionsVersion_SVN
-    ^ '$Id$'
-! !
--- a/transforms/tests/stx_goodies_xtreams_transforms_tests.st	Sun Jan 15 02:18:17 2012 +0000
+++ b/transforms/tests/stx_goodies_xtreams_transforms_tests.st	Sun Jan 15 02:18:53 2012 +0000
@@ -1,5 +1,9 @@
+'From Smalltalk/X, Version:6.2.1 on 14-01-2012 at 09:11:28 PM'                  !
+
 "{ Package: 'stx:goodies/xtreams/transforms/tests' }"
 
+"{ NameSpace: Xtreams }"
+
 LibraryDefinition subclass:#stx_goodies_xtreams_transforms_tests
 	instanceVariableNames:''
 	classVariableNames:''
@@ -33,8 +37,8 @@
 
     ^ #(
         #'stx:goodies/sunit'    "TestAsserter - superclass of Xtreams::MessagePackMarshalerTest "
-        #'stx:goodies/xtreams/core'    "Xtreams::ElasticBuffer - referenced by Xtreams::CollectionReadingWritingTest>>testWriteTransformHexToByte "
-        #'stx:goodies/xtreams/core/tests'    "Xtreams::ReadingWritingTest - superclass of extended Xtreams::CollectionReadingWritingTest "
+        #'stx:goodies/xtreams/core'    "Xtreams::Incomplete - referenced by Xtreams::ReadingWritingTest>>testReadTransformingPastEnd "
+        #'stx:goodies/xtreams/core/tests'    "Xtreams::FiniteReadingWritingTests - superclass of extended Xtreams::CollectionReadingWritingTest "
         #'stx:goodies/xtreams/terminals/tests'    "Xtreams::CollectionReadingWritingTest - extended "
         #'stx:goodies/xtreams/transforms'    "Xtreams::ObjectAnalyseStream - referenced by Xtreams::ObjectMarshalerTest>>analyse "
         #'stx:libbasic'    "Object - superclass of Xtreams::MessagePackMarshalerTest "
@@ -159,7 +163,7 @@
     "Return a SVN revision number of myself.
      This number is updated after a commit"
 
-    ^ "$SVN-Revision:"'nil'"$"
+    ^ "$SVN-Revision:"'29'"$"
 ! !
 
 !stx_goodies_xtreams_transforms_tests class methodsFor:'documentation'!