Stream.st
branchjv
changeset 18120 e3a375d5f6a8
parent 18112 0d7ac9096619
parent 17673 1ffcbe17e130
child 18334 3e18bee23c3a
--- a/Stream.st	Tue Feb 04 21:09:59 2014 +0100
+++ b/Stream.st	Wed Apr 01 10:20:10 2015 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -11,6 +13,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#Stream
 	instanceVariableNames:'signalAtEnd'
 	classVariableNames:'StreamErrorSignal PositionErrorSignal ReadErrorSignal
@@ -47,44 +51,62 @@
 
 
     Subclasses should (at least) implement:
-	#next           (if readable)
-	#nextPut:       (if writable)
-	#contents
-	#atEnd
-	#isReadable
-	#isWritable
+        #next           (if readable)
+        #nextPut:       (if writable)
+        #contents
+        #atEnd
+        #isReadable
+        #isWritable
 
     Peekable & Positionable streams should (at least) implement:
-	#peek
-	#position
-	#position:
+        #peek
+        #position
+        #position:
 
 
     [instance variables:]
-	signalAtEnd             <nil | Boolean> controls behavior when a read
-						is attempted past the end-of-stream
-						if true, the endOfStreamSignal is raised.
-						if false, nil is returned.
-						if nil (the default), the signal
-						is raised, but if there is no handler,
-						nil is returned.
+        signalAtEnd             <nil | Boolean> controls behavior when a read
+                                                is attempted past the end-of-stream
+                                                if true, the endOfStreamSignal is raised.
+                                                if false, nil is returned.
+                                                if nil (the default), the signal
+                                                is raised, but if there is no handler,
+                                                nil is returned.
         
     [Class variables / Exceptions:]
-	StreamError             <Exception>     parent of all stream errors
-
-	PositionError           <Exception>     position attemted on a stream
-						which does not support positioning,
-						or if the position is invalid.
-
-	ReadError               <Exception>     raised on read errors
-
-	WriteError              <Exception>     raised on write errors
-
-	EndOfStreamSignal       <Signal>        raised at end of stream if signalAtEnd
-						is enabled.
+        StreamError             <Exception>     parent of all stream errors
+
+        PositionError           <Exception>     position attemted on a stream
+                                                which does not support positioning,
+                                                or if the position is invalid.
+
+        ReadError               <Exception>     raised on read errors
+
+        WriteError              <Exception>     raised on write errors
+
+        EndOfStreamSignal       <Signal>        raised at end of stream if signalAtEnd
+                                                is enabled.
+
+    [caveat:]
+        The Stream hierarchy has a few little quirks in it, which are a consequence of some early historic
+        decisions. The biggest problem is the distinction between readable and writeable streams based on inheritance,
+        instead of by either using state (i.e. a flag) or delegation.
+        The problem is that there are streams which can be both, and maybe even dynamically change their opinion,
+        on whether being readable/writable. 
+        (For example, a buffer may be write-only while filled, but become readonly, when given to a consumer.)
+
+        The above decision to base this on inheritance lead to the ugly ReadStream - WriteStream - ReadWriteStream
+        hierarchy, with some subclasses undoing the blocking of their superclass.
+
+        Classes named 'ReadStream', 'WriteStream', 'ReadWriteStream', 'PeekableStream' and 'PositionableStream' should 
+        all be eliminated in favour of a few flags in the 'Stream' superclass.
+
+        It is really time for a new stream hierarchy (XStreams, for example).
+        (On the other hand: there is so much code around, which depends on the current situation, that such a change
+         must really be thought through - most got used to these issues and live with it more or less happily)
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 "
 ! !
 
@@ -194,7 +216,14 @@
     ^ ChunkSeparator
 ! !
 
-
+!Stream methodsFor:'Compatibility-Dolphin'!
+
+display:someObject
+    "dolphin compatibility"
+
+    "/ someObject printOn:self.
+    self nextPutAll: someObject asString.
+! !
 
 
 !Stream methodsFor:'accessing'!
@@ -225,8 +254,7 @@
     "set the signalAtEnd flag setting. If true, reading past the end
      will raise an EndOfStream exception. If false, no exception is
      raised and nil is returned from all reading messages.
-     The default is to raise a signal, but return nil if
-     not handled."
+     The default is to raise a signal, but return nil if not handled (st80 compatibility)."
 
     signalAtEnd := aBoolean.
 
@@ -245,13 +273,13 @@
 
      s := '12' readStream.
      Stream endOfStreamSignal handle:[:ex |
-	Transcript showCR:'end reached'.
-	ex return
+        Transcript showCR:'end reached'.
+        ex return
      ] do:[
-	Transcript showCR:s next.
-	Transcript showCR:s next.
-	Transcript showCR:s next.
-	Transcript showCR:s next.
+        Transcript showCR:s next.
+        Transcript showCR:s next.
+        Transcript showCR:s next.
+        Transcript showCR:s next.
      ]
     "
 
@@ -273,30 +301,25 @@
      s := '12' readStream.
      s signalAtEnd:false.
      Stream endOfStreamSignal handle:[:ex |
-	Transcript showCR:'end reached'.
-	ex return
+        Transcript showCR:'end reached'.
+        ex return
      ] do:[
-	Transcript showCR:s next.
-	Transcript showCR:s next.
-	Transcript showCR:s next.
-	Transcript showCR:s next.
+        Transcript showCR:s next.
+        Transcript showCR:s next.
+        Transcript showCR:s next.
+        Transcript showCR:s next.
      ]
     "
 
     "Modified: / 16.6.1998 / 16:04:41 / cg"
 ! !
 
-!Stream methodsFor:'closing'!
-
-close
-    "close the stream - nothing done here.
-     Added for compatibility with external streams."
-
-    ^ self
-! !
-
 !Stream methodsFor:'converting'!
 
+asLineNumberReadStream
+    ^ LineNumberReadStream on:self
+!
+
 asStream
     ^ self
 ! !
@@ -569,6 +592,13 @@
     ^ false.
 !
 
+eolMode
+    "Dummy here, but added to make internalStreams protocol compatible 
+     with externalStreams."
+
+     ^ nil  "/ transparent
+!
+
 eolMode:aSymbol
     "Ignored here, but added to make internalStreams protocol compatible 
      with externalStreams."
@@ -579,6 +609,11 @@
      with externalStreams."
 !
 
+lineEndLF
+    "Ignored here, but added to make internalStreams protocol compatible 
+     with externalStreams."
+!
+
 lineEndTransparent
     "Ignored here, but added to make internalStreams protocol compatible 
      with externalStreams."
@@ -692,11 +727,12 @@
     "read from the receiver, and write all data up to the end to another stream.
      Return the number of bytes which have been transferred"
 
-    |bufferSpecies buffer bytesWritten readCount writeCount count freeBuffer|
-
-    bytesWritten := 0.
+    |bufferSpecies buffer countWritten freeBuffer|
+
+    countWritten := 0.
     bufferSpecies := self contentsSpecies.
     bufferSpecies == ByteArray ifTrue:[
+        "an ExternalBytes buffer is faster when writing to a windows ExternalStream"
         buffer:= ExternalBytes unprotectedNew:bufferSize.
         freeBuffer := true.
     ] ifFalse:[
@@ -704,16 +740,23 @@
         freeBuffer := false.
     ].
 
-    "Note: atEnd will block if reading from an empty pipe or socket"
-    [self atEnd] whileFalse:[ 
-        readCount := self nextAvailableBytes:bufferSize into:buffer startingAt:1.
+    "read loop: read until end of stream"
+    [
+        |readCount|
+
+        readCount := self nextAvailable:bufferSize into:buffer startingAt:1.
         readCount > 0 ifTrue:[
+            |writeCount|
+
             writeCount := 0.
+            "write loop: write until all is written"
             [
-                count := outStream nextPutBytes:readCount-writeCount
-                                    from:buffer 
-                                    startingAt:writeCount+1.
-                bytesWritten := bytesWritten + count.
+                |count|
+
+                count := outStream 
+                            nextPutAll:readCount-writeCount
+                            from:buffer 
+                            startingAt:writeCount+1.
                 writeCount := writeCount + count.
                 writeCount < readCount ifTrue:[
                     outStream writeWait.
@@ -722,17 +765,22 @@
                     false
                 ].
             ] whileTrue.
-        ] 
-    ].
+            countWritten := countWritten + writeCount.
+        ]. 
+        "Note: atEnd will block if reading from an empty pipe or socket.
+         avoid atEnd if possible, because it reads a single byte."
+        readCount ~~ 0 or:[self atEnd not]
+    ] whileTrue.
+
     freeBuffer ifTrue:[ buffer free ].
-    ^ bytesWritten
+    ^ countWritten
 
     "
       'hello world' readStream copyToEndInto:'/tmp/mist' asFilename writeStream.
       'hello world' readStream copyToEndInto:#[] writeStream.
       ('/tmp/mist' asFilename readStream binary; yourself) copyToEndInto:#[] writeStream
       #[1 2 3 4 5 6 7] readStream copyToEndInto:'/tmp/mist' asFilename writeStream.
-      #[1 2 3 4 5 6 7] readStream copyToEndInto:'' writeStream.
+      #(1 2 3 a 'b' 6.4 true) readStream next; copyToEndInto:#() writeStream inspect.
 
     "
 ! !
@@ -805,23 +853,13 @@
              with externalStreams - it is normally not used with other
              streams."
 
-    |n "{Class: SmallInteger }"
-     dstIndex|
-
-    numBytes == 0 ifTrue:[
-        ^ 0.
-    ].
-
-    dstIndex := initialIndex.
+    |n "{Class: SmallInteger }"|
+
     n := 0.
 
-    [self atEnd] whileFalse:[
-        aCollection byteAt:dstIndex put:self nextByte.
+    [n ~= numBytes and:[self atEnd not]] whileTrue:[
+        aCollection byteAt:initialIndex+n put:self nextByte.
         n := n + 1.
-        n == numBytes ifTrue:[
-            ^ n
-        ].
-        dstIndex := dstIndex + 1.
     ].
     ^ n
 
@@ -836,6 +874,18 @@
      Transcript showCR:('n = %1; buffer = <%2>' bindWith:n with:buffer)
     "
 
+    "
+     |s n buffer|
+
+     buffer := String new:10.
+
+     s := ReadStream on:'Hello World'.
+     s next:6.
+     n := s nextBytes:5 into:buffer startingAt:1.
+     Transcript showCR:('n = %1; buffer = <%2>' bindWith:n with:buffer)
+    "
+
+
     "Modified: 22.4.1997 / 10:43:08 / cg"
 !
 
@@ -965,12 +1015,24 @@
     ^ Float readBinaryIEEEDoubleFrom:self
 !
 
+nextIEEEDoubleMSB:msbFirst
+    "read an 8-byte IEEE double precision float number"
+
+    ^ Float readBinaryIEEEDoubleFrom:self MSB:msbFirst
+!
+
 nextIEEESingle
     "read a 4-byte IEEE single precision float number"
 
     ^ ShortFloat readBinaryIEEESingleFrom:self
 !
 
+nextIEEESingleMSB:msbFirst
+    "read a 4-byte IEEE single precision float number"
+
+    ^ ShortFloat readBinaryIEEESingleFrom:self MSB:msbFirst
+!
+
 nextLongMSB:msbFlag
     "return a signed long (4 bytes) from the stream.
      The receiver must support reading of binary bytes.
@@ -1055,8 +1117,8 @@
      The msbFlag argument controls if the integer is to be read with
      most-significant-byte-first (true) or least-first (false).
      This interface is provided to allow talking to external programs,
-     where its known that the byte order is some definite one.
-     If you dont care (i.e. talk to other smalltalks) or you can control the
+     where it's known that the byte order is some definite one.
+     If you don't care (i.e. talk to other smalltalks) or you can control the
      order, please use the corresponding xxxNet methods, which use a standard
      network byte order."
 
@@ -1401,16 +1463,22 @@
 nextPutAllUtf16:aString
     "write a string as UTF-16 bytes"
 
-    aString do:[:eachCharacter|
-        self nextPutUtf16:eachCharacter.
+    |sz "{Class: SmallInteger}"|
+
+    sz := aString size.
+    1 to:sz do:[:idx|
+        self nextPutUtf16:(aString at:idx).
     ].
 !
 
 nextPutAllUtf8:aString
     "normal streams can not handle multi-byte characters, so convert them to utf8"
 
-    aString do:[:eachCharacter|
-        self nextPutUtf8:eachCharacter.
+    |sz "{Class: SmallInteger}"|
+
+    sz := aString size.
+    1 to:sz do:[:idx|
+        self nextPutUtf8:(aString at:idx).
     ].
 !
 
@@ -1563,13 +1631,25 @@
 nextPutIEEEDouble:aFloat
     "write an 8-byte IEEE double precision float number"
 
-    Float storeBinaryIEEEDouble:aFloat on:self
+    Float storeBinaryIEEEDouble:aFloat on:self MSB:(UninterpretedBytes isBigEndian)
+!
+
+nextPutIEEEDouble:aFloat MSB:msb
+    "write an 8-byte IEEE double precision float number"
+
+    Float storeBinaryIEEEDouble:aFloat on:self MSB:msb
 !
 
 nextPutIEEESingle:aFloat
     "write a 4-byte IEEE single precision float number"
 
-    ShortFloat storeBinaryIEEESingle:aFloat on:self
+    ShortFloat storeBinaryIEEESingle:aFloat on:self MSB:(UninterpretedBytes isBigEndian).
+!
+
+nextPutIEEESingle:aFloat MSB:msb
+    "write a 4-byte IEEE single precision float number"
+
+    ShortFloat storeBinaryIEEESingle:aFloat on:self MSB:msb.
 !
 
 nextPutLong:aNumber MSB:msbFlag
@@ -1726,7 +1806,7 @@
      UTF-16 can encode only characters with code points between 0 to 16r10FFFF.
      The collection must be able to store 2-byte values (TwoByteString, OrderedCollection)"
 
-    |codePoint|
+    |codePoint "{Class: SmallInteger}"|
 
     codePoint := aCharacter codePoint.
     (codePoint <= 16rD7FF
@@ -1747,7 +1827,7 @@
     "
         ((WriteStream on:Unicode16String new)
             nextPutUtf16:$B;
-            nextPutUtf16:$Ä; 
+            nextPutUtf16:$Ä; 
             nextPutUtf16:(Character codePoint:16r10CCCC)
             yourself) contents
     "
@@ -1758,7 +1838,9 @@
      Up to 31 bits can be encoded in up to 6 bytes.
      However, currently, characters are limited to 31 bits."
 
-    |codePoint b1 b2 b3 b4 b5 v|
+    |codePoint "{Class: SmallInteger}"
+     v "{Class: SmallInteger}"
+     b1 b2 b3 b4 b5|
 
     codePoint := aCharacter codePoint.
 
@@ -1803,13 +1885,12 @@
         ^ self.
     ].
 
-
-    self error:'codePoint > 31bit in #nextPutUtf8:'.
+    EncodingError raiseWith:aCharacter errorString:'codePoint > 31bit in #nextPutUtf8:'.
 
     "
       (String streamContents:[:s| 
             s nextPutUtf8:$a.
-            s nextPutUtf8:$ü.
+            s nextPutUtf8:$ü.
             s nextPutUtf8: (Character value:16r1fff).
             s nextPutUtf8: (Character value:16rffff).
             s nextPutUtf8: (Character value:16r1ffffff).
@@ -1854,6 +1935,15 @@
     "Modified: 10.1.1996 / 19:39:19 / cg"
 ! !
 
+!Stream methodsFor:'open / close'!
+
+close
+    "close the stream - nothing done here.
+     Added for compatibility with external streams."
+
+    ^ self
+! !
+
 !Stream methodsFor:'private'!
 
 contentsSpecies
@@ -1870,6 +1960,14 @@
 
 !Stream methodsFor:'queries'!
 
+canReadWithoutBlocking
+    ^ true
+!
+
+canWriteWithoutBlocking
+    ^ true
+!
+
 current
     "for compatibility with Transcript - allow Transcript current,
      even if redirected to the standardError"
@@ -2052,6 +2150,36 @@
     "Modified: 15.5.1996 / 17:57:58 / cg"
 !
 
+next:numObjects into:aCollection startingAt:initialIndex
+    "return the next numObjects from the stream."
+
+    |n "{Class: SmallInteger }"|
+
+    n := 0.
+
+    [n ~~ numObjects] whileTrue:[
+        self atEnd ifTrue:[
+            ^ aCollection copyFrom:1 to:initialIndex+n-1.
+        ].
+        aCollection at:(initialIndex + n) put:self next.
+        n := n + 1.
+    ].
+    ^ aCollection.
+
+    "
+     |s n buffer|
+
+     buffer := Array new:10.
+
+     s := ReadStream on:#(1 2 3 4 5 6 7 8 9).
+     s next:3.
+     n := s next:9 into:buffer startingAt:2.
+     Transcript showCR:('n = %1; buffer = %2' bindWith:n with:buffer)
+    "
+
+    "Modified: 22.4.1997 / 10:43:08 / cg"
+!
+
 nextAvailable:count
     "return the next count elements of the stream as aCollection.
      If the stream reaches the end before count elements have been read,
@@ -2081,6 +2209,20 @@
     "Modified: / 16.6.1998 / 15:52:41 / cg"
 !
 
+nextAvailable:numObjects into:aCollection startingAt:initialIndex
+    "return the next numObjects from the stream."
+
+    |n "{Class: SmallInteger }"|
+
+    n := 0.
+
+    [n ~= numObjects and:[self atEnd not]] whileTrue:[
+        aCollection at:(initialIndex + n) put:self next.
+        n := n + 1.
+    ].
+    ^ n.
+!
+
 nextMatchFor:anObject
     "read an element from the receiver, return true if it was equal to
      the argument, anObject; false otherwise."
@@ -2114,12 +2256,12 @@
 skip:numberToSkip 
     "skip numberToSkip objects, return the receiver"
 
-    "dont know how to unread ..."
+    "don't know how to unread ..."
     numberToSkip < 0 ifTrue:[
         PositionError raiseRequest.
         ^ self
     ].
-    numberToSkip timesRepeat:self next
+    numberToSkip timesRepeat:[self next]
 
     "
      |s|
@@ -2539,16 +2681,18 @@
      See also #upToAll:, which returns the same, but leaves the
      read pointer before the matched subcollection."
 
-    |answerStream element last rslt|
+    |answerStream element last|
 
     last := aCollection last.
-    answerStream := WriteStream on:(self contentsSpecies new).
-    [self atEnd] whileFalse:[
-        element := self next.
+    answerStream := ReadWriteStream on:(self contentsSpecies new).
+    [(element := self nextOrNil) notNil] whileTrue:[
         answerStream nextPut:element.
         element == last ifTrue:[
-            ((rslt := answerStream contents) endsWith:aCollection) ifTrue:[
-                ^ rslt copyButLast:aCollection size
+            (answerStream contents endsWith:aCollection) ifTrue:[
+                |pos|
+                pos := answerStream position.
+                answerStream resetPosition.
+                ^ answerStream next:pos-aCollection size.
             ]
         ].
     ].
@@ -2602,7 +2746,7 @@
      The next read operation will return the matching element.
      If no such element is encountered, all elements up to the end are read
      and returned.
-     This returns the exact same as upToAny: would, but leaves the streams position so that
+     This returns the exact same as upToAny: would, but leaves the stream's position so that
      the next read returns the matching delimiter instead of skipping it.
      Caveat: this is the one which should have been called upTo: in the first place;
      however, it seems now too late for a change."
@@ -2636,7 +2780,8 @@
 upToElementForWhich:aBlock
     "read elements until aBlock returns true for an element. 
      Return the collected elements excluding that element.
-     Leave the stream positioned for the next read to return that element."                                                             
+     Leave the stream positioned for the next read to return that element.
+     If no element matches, all elements up to the end are returned"                                                             
 
     |answerStream next|
 
@@ -2677,6 +2822,65 @@
     "
 
     "Modified: 15.5.1996 / 18:00:39 / cg"
+!
+
+upToMatching:aBlock
+    "Return the next elements up to but not including the next element
+     for which aBlock returns true.
+     The next read will return that matching element.
+     If none matches, the remaining elements up to the end are returned."
+
+    ^ self upToElementForWhich:aBlock
+"/    |answerStream element|
+"/
+"/    answerStream := WriteStream on:(self contentsSpecies new).
+"/    [self atEnd] whileFalse: [
+"/        element := self peek.
+"/        (aBlock value:element) ifTrue: [^ answerStream contents].
+"/        answerStream nextPut:element.
+"/        self next.
+"/    ].
+"/    ^ answerStream contents
+
+    "
+     'hello world' readStream upToMatching:[:c | c isSeparator].  
+    "
+    "
+     'helloworld' readStream upToMatching:[:c | c isSeparator].   
+    "
+    "
+     |s|
+
+     s := 'hello world' readStream.
+     s upToMatching:[:c | c isSeparator].
+     s upToEnd
+    "
+
+    "Modified: 26.2.1997 / 12:20:57 / cg"
+!
+
+upToSeparator
+    "Return the next elements up to but not including the next separator.
+     The next read will return the separator.
+     If no separator is encountered, the contents up to the end is returned.
+     The elements are supposed to understand #isSeparator 
+     (i.e. the receiver is supposed to be a character-stream)."
+
+    ^ self upToElementForWhich:[:ch | ch isSeparator]
+
+    "
+     'hello world' readStream upToSeparator  
+     'helloworld' readStream upToSeparator   
+     'helloworld' readStream upToSeparator   
+     '' readStream upToSeparator   
+
+     |s|
+     s := 'hello world' readStream.
+     s upToSeparator.
+     s upToEnd  
+    "
+
+    "Modified: 4.1.1997 / 23:38:05 / cg"
 ! !
 
 !Stream methodsFor:'reading-strings'!
@@ -2731,6 +2935,10 @@
     ^ false
 !
 
+isLineNumberReadStream
+    ^ false
+!
+
 isPositionable
     "return true, if the stream supports positioning (some do not).
      Since this is an abstract class, false is returned here - just to make certain."
@@ -2788,6 +2996,8 @@
 !Stream methodsFor:'visiting'!
 
 acceptVisitor:aVisitor with:aParameter
+    "dispatch for visitor pattern; send #visitStream:with: to aVisitor."
+
     ^ aVisitor visitStream:self with:aParameter
 ! !
 
@@ -2807,7 +3017,7 @@
     ^ self readWaitWithTimeoutMs:timeout
 !
 
-readWaitWithTimeout:seconds
+readWaitWithTimeout:secondsOrTimeDuration
     "suspend the current process, until the receiver
      becomes ready for reading or a timeout (in seconds) expired.
      If data is already available, return immediate.
@@ -2817,8 +3027,12 @@
 
     |ms|
 
-    seconds notNil ifTrue:[
-        ms := seconds * 1000
+    secondsOrTimeDuration notNil ifTrue:[
+        secondsOrTimeDuration isNumber ifTrue:[
+            ms := secondsOrTimeDuration * 1000.
+        ] ifFalse:[
+            ms := secondsOrTimeDuration getMilliseconds.
+        ]
     ].
     ^ self readWaitWithTimeoutMs:ms
 !
@@ -2861,7 +3075,7 @@
     ^ self writeWaitWithTimeoutMs:timeout
 !
 
-writeWaitWithTimeout:timeout
+writeWaitWithTimeout:secondsOrTimeDuration
     "suspend the current process, until the receiver
      becomes ready for writing or a timeout (in seconds) expired.
      Return true if a timeout occured (i.e. false, if data is available).
@@ -2870,8 +3084,12 @@
 
     |ms|
 
-    timeout notNil ifTrue:[
-	ms := timeout * 1000
+    secondsOrTimeDuration notNil ifTrue:[
+        secondsOrTimeDuration isNumber ifTrue:[
+            ms := secondsOrTimeDuration * 1000.
+        ] ifFalse:[
+            ms := secondsOrTimeDuration getMilliseconds.
+        ]
     ].
     ^ self writeWaitWithTimeoutMs:ms
 !
@@ -2961,6 +3179,24 @@
     "Modified: 7.5.1996 / 23:54:53 / stefan"
 !
 
+format:formatSpec with:args
+    "convenient formatted printing:
+        %1..%9  - positional parameters from args-collection
+        %(name) - named parameter from args-dictionary
+        %%      - escape for %
+        %<cr>   - cr (also tab, nl)"
+
+    formatSpec expandPlaceholders:$% with:args on:self
+
+    "
+     1 to: 10 do:[:i |
+        Transcript 
+            format:'[%1] Hello %2 World - this is %3%<cr>' 
+            with:{i . 'my' . 'nice'}
+     ].
+    "
+!
+
 next:count put:anObject
     "put the argument, anObject count times onto the receiver.
      This is only allowed, if the receiver supports writing."
@@ -3014,9 +3250,7 @@
     "put all elements of the argument, aCollection onto the receiver.
      This is only allowed, if the receiver supports writing."
 
-    aCollection do:[:element |
-        self nextPut:element
-    ].
+    self nextPutAll:aCollection startingAt:1 to:aCollection size
 
     "
      |s|
@@ -3040,6 +3274,28 @@
     "Modified: 11.7.1996 / 10:00:21 / cg"
 !
 
+nextPutAll:count from:aCollection startingAt:initialIndex
+    "append count elements with index starting at initialIndex
+     of the argument, aCollection onto the receiver.
+     This is only allowed, if the receiver supports writing.
+     Answer the number of elements that were appended.
+     This is for compatibility with ExternalStream, where less then 
+     count elements may be written. Dolphin defines this as well."
+
+    self nextPutAll:aCollection startingAt:initialIndex to:initialIndex+count-1.
+    ^ count
+
+    "
+     |s|
+
+     s := WriteStream on:#().
+     s nextPutAll:4 from:#('one' 'two' 'three' 'four' 'five') startingAt:2.
+     s contents
+    "
+
+    "Modified: 11.7.1996 / 10:00:32 / cg"
+!
+
 nextPutAll:aCollection startingAt:first
     "append the elements starting with index to the end
      of the argument, aCollection onto the receiver.
@@ -3115,7 +3371,7 @@
 
 nextPutLine:aCollection
     "put all elements of the argument, aCollection onto the receiver,
-     and append a cr (carriage return). 
+     and append a cr (carriage return). aCollection should contain characters.
      This is only useful with character streams in textMode,
      and only allowed, if the receiver supports writing."
 
@@ -3163,6 +3419,20 @@
     "Created: / 26-09-2012 / 18:21:06 / cg"
 !
 
+println
+    "for those used to Java/Javascript, a compatibility message.
+     Most useful inside expecco"
+
+    self cr
+!
+
+println:anObject
+    "for those used to Java/Javascript, a compatibility message.
+     Most useful inside expecco"
+
+    self showCR:anObject
+!
+
 show:something
     "append a printed representation of the argument to the stream.
      This makes streams somewhat compatible to TextCollectors and
@@ -3225,6 +3495,19 @@
     "Created: / 19-08-2010 / 15:42:25 / cg"
 !
 
+show:something with:arg1 with:arg2 with:arg3 with:arg4 with:arg5
+    "append a printed representation of the argument to the stream, expanding
+     the placeHolders %1,%2 and %3 with the printStrings of arg1, arg2 and arg3.
+     This makes streams somewhat compatible to TextCollectors and
+     allows you to say: 
+        Smalltalk at:#Transcript put:Stdout
+     or to use #show:/#showCR: with internal or external streams."
+
+    self show:(something bindWith:arg1 with:arg2 with:arg3 with:arg4 with:arg5)
+
+    "Created: / 19-08-2010 / 15:42:25 / cg"
+!
+
 show:something withArguments:args
     "append a printed representation of the argument to the stream, expanding
      the placeHolders %1,%2 and %3 with the printStrings of argi.
@@ -3303,6 +3586,19 @@
     "Created: / 19-08-2010 / 15:42:50 / cg"
 !
 
+showCR:something with:arg1 with:arg2 with:arg3 with:arg4 with:arg5
+    "append a printed representation of the argument to the stream, expanding
+     the placeHolders %1,%2 and %3 with the printStrings of arg1, arg2 and arg3.
+     This makes streams somewhat compatible to TextCollectors and
+     allows you to say: 
+        Smalltalk at:#Transcript put:Stdout
+     or to use #show:/#showCR: with internal or external streams."
+
+    self showCR:(something bindWith:arg1 with:arg2 with:arg3 with:arg4 with:arg5)
+
+    "Created: / 19-08-2010 / 15:42:50 / cg"
+!
+
 showCR:something withArguments:args
     "append a printed representation of the argument to the stream, expanding
      the placeHolders %1,%2 and %3 with the printStrings of argi.
@@ -3427,55 +3723,54 @@
     stop := endIndex + 1.
 
     [index <= endIndex] whileTrue:[
-	"
-	 find position of next interesting character; 
-	 output stuff up to that one in one piece
-	"
-	next := aString indexOfAny:stopChars startingAt:index ifAbsent:stop.
-
-	((index == 1) and:[next == stop]) ifTrue:[
-	    self nextPutAll:aString
-	] ifFalse:[
-	    self nextPutAll:aString startingAt:index to:(next - 1)
-	].
-
-	index := next.
-	(index <= endIndex) ifTrue:[
-	    character := aString at:index.
-
-	    (character == ${ ) ifTrue:[
-		"/ starts a primitive
-		((index > 1) and:[(aString at:index-1) == $%]) ifTrue:[
-		    inPrimitive := true
-		]
-	    ] ifFalse:[
-		"/ ends a primitive
-		(character == $} ) ifTrue:[
-		    ((index > 1) and:[(aString at:index-1) == $%]) ifTrue:[
-			inPrimitive := false
-		    ]
-		] ifFalse:[
-		    "/
-		    "/ exclas have to be doubled - except if within a primitive
-		    "/
-		    inPrimitive ifFalse:[
-			(character == sep) ifTrue:[
-			    self nextPut:sep
-			]
-		    ]
-		]
-	    ].
-
-	    self nextPut:character.
-	    index := index + 1.
-	].
+        "
+         find position of next interesting character; 
+         output stuff up to that one in one piece
+        "
+        next := aString indexOfAny:stopChars startingAt:index ifAbsent:stop.
+
+        ((index == 1) and:[next == stop]) ifTrue:[
+            self nextPutAll:aString
+        ] ifFalse:[
+            self nextPutAll:aString startingAt:index to:(next - 1)
+        ].
+
+        index := next.
+        (index <= endIndex) ifTrue:[
+            character := aString at:index.
+
+            (character == ${ ) ifTrue:[
+                "/ starts a primitive
+                ((index > 1) and:[(aString at:index-1) == $%]) ifTrue:[
+                    inPrimitive := true
+                ]
+            ] ifFalse:[
+                "/ ends a primitive
+                (character == $} ) ifTrue:[
+                    ((index > 1) and:[(aString at:index-1) == $%]) ifTrue:[
+                        inPrimitive := false
+                    ]
+                ] ifFalse:[
+                    "/
+                    "/ exclas have to be doubled - except if within a primitive
+                    "/
+                    inPrimitive ifFalse:[
+                        (character == sep) ifTrue:[
+                            self nextPut:sep
+                        ]
+                    ]
+                ]
+            ].
+
+            self nextPut:character.
+            index := index + 1.
+        ].
     ].
     (aString endsWith:Character cr) ifFalse:[
-	self cr.
+        self cr.
     ].
 
     "Modified: / 21.4.1998 / 17:22:47 / cg"
-    "/ foo
 !
 
 nextPutChunkSeparator
@@ -3489,11 +3784,11 @@
 !Stream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Stream.st,v 1.212 2013-12-02 19:05:57 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Stream.st,v 1.242 2015-03-25 22:28:27 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Stream.st,v 1.212 2013-12-02 19:05:57 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Stream.st,v 1.242 2015-03-25 22:28:27 cg Exp $'
 ! !