Stream.st
branchjv
changeset 20244 20922299fd44
parent 20206 51652e7f46dd
parent 20242 92d211a6151f
child 20342 219a5a47e8b1
--- a/Stream.st	Thu Aug 11 06:44:08 2016 +0200
+++ b/Stream.st	Fri Aug 12 06:44:59 2016 +0200
@@ -237,8 +237,8 @@
 !
 
 signalAtEnd
-    "return the signalAtEnd flag setting. 
-     If true, reading past the end will always raise an EndOfStream exception. 
+    "return the signalAtEnd flag setting.
+     If true, reading past the end will always raise an EndOfStream exception.
      If false, no exception is raised and nil is returned from all reading messages.
      If nil (default), the exception is raised if there is a handler; otherwise, nil is returned.
      The default is nil (for ST80 compatibility) i.e. to only raise a signal if there is a handler."
@@ -317,7 +317,7 @@
 
 asLineNumberReadStream
     "returns a new stream, which keeps track of the line number.
-     It can be asked for the current linenumber, 
+     It can be asked for the current linenumber,
      which is useful eg. for error message generation"
 
     ^ LineNumberReadStream on:self
@@ -367,7 +367,7 @@
     "Created: 14.5.1996 / 17:38:07 / cg"
 !
 
-italic 
+italic
     "set emphasis to #italic.
      this allows Streams to be used interchangeable with printStreams"
 
@@ -459,7 +459,7 @@
     "
 
     "
-     Filename readingFile:'/etc/hosts' 
+     Filename readingFile:'/etc/hosts'
      do:[:s |
          s linesDo:[:line | Transcript showCR:line].
      ].
@@ -506,9 +506,9 @@
 
 pastEndRead
     "someone tried to read after the end of the stream.
-     If signalAtEnd == true, raise a signal. 
+     If signalAtEnd == true, raise a signal.
      If it is false, return nil.
-     Otherwise raise a notification, which is ignored if not handled; 
+     Otherwise raise a notification, which is ignored if not handled;
      otherwise return nil."
 
     |shouldSignalAtEnd|
@@ -592,7 +592,7 @@
     "switch to binary mode. In binary mode, reading of text streams
      returns byte-valued integers instead of characters; writing expects
      byte-valued integers respectively.
-     Ignored here, but added to make internalStreams protocol compatible 
+     Ignored here, but added to make internalStreams protocol compatible
      with externalStreams."
 
     "Modified: 15.5.1996 / 17:38:36 / cg"
@@ -606,29 +606,29 @@
 !
 
 eolMode
-    "Dummy here, but added to make internalStreams protocol compatible 
+    "Dummy here, but added to make internalStreams protocol compatible
      with externalStreams."
 
      ^ nil  "/ transparent
 !
 
 eolMode:aSymbol
-    "Ignored here, but added to make internalStreams protocol compatible 
+    "Ignored here, but added to make internalStreams protocol compatible
      with externalStreams."
 !
 
 lineEndCRLF
-    "Ignored here, but added to make internalStreams protocol compatible 
+    "Ignored here, but added to make internalStreams protocol compatible
      with externalStreams."
 !
 
 lineEndLF
-    "Ignored here, but added to make internalStreams protocol compatible 
+    "Ignored here, but added to make internalStreams protocol compatible
      with externalStreams."
 !
 
 lineEndTransparent
-    "Ignored here, but added to make internalStreams protocol compatible 
+    "Ignored here, but added to make internalStreams protocol compatible
      with externalStreams."
 !
 
@@ -639,8 +639,8 @@
 !
 
 text
-    "switch to text mode. 
-     Ignored here, but added to make internalStreams protocol compatible 
+    "switch to text mode.
+     Ignored here, but added to make internalStreams protocol compatible
      with externalStreams."
 
     "Modified: 15.5.1996 / 17:38:36 / cg"
@@ -691,9 +691,9 @@
             [
                 |count|
 
-                count := aWriteStream 
+                count := aWriteStream
                             nextPutAll:readCount-writeCount
-                            from:buffer 
+                            from:buffer
                             startingAt:writeCount+1.
                 writeCount := writeCount + count.
                 writeCount < readCount ifTrue:[
@@ -704,7 +704,7 @@
                 ].
             ] 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."
         bytesLeft ~~ 0 or:[self atEnd not]
@@ -742,8 +742,8 @@
 "/    retVal := self copyToEndInto:outStream bufferSize:(64*1024).
 "/].
 "/
-"/Transcript showCR:('%1 KB copied in %2s (%3 KB/s)' 
-"/        bindWith:((retVal/1024)asFixedPoint:2) 
+"/Transcript showCR:('%1 KB copied in %2s (%3 KB/s)'
+"/        bindWith:((retVal/1024)asFixedPoint:2)
 "/        with:((t/1000)asFixedPoint:2)
 "/        with:((retVal/1024/(t/1000))asFixedPoint:2)).
 "/^ retVal.
@@ -780,9 +780,9 @@
             [
                 |count|
 
-                count := outStream 
+                count := outStream
                             nextPutAll:readCount-writeCount
-                            from:buffer 
+                            from:buffer
                             startingAt:writeCount+1.
                 writeCount := writeCount + count.
                 writeCount < readCount ifTrue:[
@@ -793,7 +793,7 @@
                 ].
             ] 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]
@@ -855,13 +855,13 @@
      If the receiver is some socket/pipe-like stream, an exception
      is raised if the connection is broken.
 
-     The object must have non-pointer indexed instvars (i.e. it must be 
+     The object must have non-pointer indexed instvars (i.e. it must be
      a ByteArray, String, Float- or DoubleArray).
      If anObject is a string or byteArray and reused, this provides the
      fastest possible physical I/O (since no new objects are allocated).
 
      Use with care - non object oriented i/o.
-     Warning: in general, you cannot use this method to pass data from other 
+     Warning: in general, you cannot use this method to pass data from other
      architectures since it does not care for byte order or float representation."
 
     ^ self nextBytes:count into:anObject startingAt:1
@@ -948,19 +948,19 @@
      If the receiver is some socket/pipe-like stream, an exception
      is raised if the connection is broken.
 
-     The object to read into must have non-pointer indexed instvars 
-     (i.e. it must be a ByteArray, String, Float- or DoubleArray).     
+     The object to read into must have non-pointer indexed instvars
+     (i.e. it must be a ByteArray, String, Float- or DoubleArray).
      If anObject is a string or byteArray and reused, this provides the
      fastest possible physical I/O (since no new objects are allocated).
 
      Use with care - non object oriented i/o.
-     Warning: in general, you cannot use this method to pass data from other 
+     Warning: in general, you cannot use this method to pass data from other
      architectures since it does not care for byte order or float representation."
 
     ^ self nextBytes:(anObject byteSize) into:anObject startingAt:1
 
     " to read 100 bytes from a stream:
-    
+
      |b aStream|
 
      aStream := 'smalltalk.rc' asFilename readStream.
@@ -1035,7 +1035,7 @@
     ].
     "change from unsigned 0..FFFF to signed -8000..7FFF"
     uval >= 16r8000 ifTrue:[
-        ^ uval - 16r10000 
+        ^ uval - 16r10000
     ].
     ^ uval
 
@@ -1059,7 +1059,7 @@
     uval := self nextUnsignedInt24MSB:msbFlag.
     "change from unsigned 0..FFFFFF to signed -800000..7FFFFF"
     uval >= 16r800000 ifTrue:[
-        ^ uval - 16r1000000 
+        ^ uval - 16r1000000
     ].
     ^ uval
 
@@ -1105,7 +1105,7 @@
     "change from unsigned 0..FFFFFFFF to signed -80000000..7FFFFFFF"
 
     val >= 16r80000000 ifTrue:[
-      ^ val - 16r100000000 
+      ^ val - 16r100000000
     ].
     ^ val
 
@@ -1152,7 +1152,7 @@
     "change from unsigned 0..FF..FF to signed -80..00..7FF..FF"
 
     uval >= 16r8000000000000000 ifTrue:[
-      ^ uval - 16r10000000000000000 
+      ^ uval - 16r10000000000000000
     ].
     ^ uval
 
@@ -1196,7 +1196,7 @@
     uval := self nextByte.
     "change from unsigned 0..FF to signed -80..7F"
     uval >= 16r80 ifTrue:[
-        ^ uval - 16r100 
+        ^ uval - 16r100
     ].
     ^ uval
 
@@ -1207,7 +1207,7 @@
 
 nextString:count
     "read the next count bytes and return it as a string.
-     If EOF is encountered while reading, a truncated string is returned. 
+     If EOF is encountered while reading, a truncated string is returned.
      If EOF is already reached before the first byte can be read,
      an error is raised."
 
@@ -1259,7 +1259,7 @@
     "/ bytes
     bytes := self nextBytes:numBytes.
     ^ (LargeInteger digitBytes:bytes MSB:msbFlag) compressed
-    
+
 "/    val := 0.
 "/    msbFlag ifTrue:[
 "/        numBytes timesRepeat:[
@@ -1278,14 +1278,14 @@
      |s|
 
      s := #[ 16r01 16r02 16r03 16r04 16r05 ] readStream.
-     (s nextUnsigned:3 MSB:true) hexPrintString.           
+     (s nextUnsigned:3 MSB:true) hexPrintString.
      s := #[ 16r01 16r02 16r03 16r04 16r05 16r06 16r07 16r08 16r09 ] readStream.
-     (s nextUnsigned:9 MSB:true) hexPrintString.           
+     (s nextUnsigned:9 MSB:true) hexPrintString.
 
      s := #[ 16r01 16r02 16r03 16r04 16r05 ] readStream.
-     (s nextUnsigned:3 MSB:false) hexPrintString.      
+     (s nextUnsigned:3 MSB:false) hexPrintString.
      s := #[ 16r01 16r02 16r03 16r04 16r05 16r06 16r07 16r08 16r09 ] readStream.
-     (s nextUnsigned:9 MSB:false) hexPrintString.      
+     (s nextUnsigned:9 MSB:false) hexPrintString.
     "
 !
 
@@ -1352,7 +1352,7 @@
         bH := b3.
         bM := b2.
         bL := b1.
-    ].    
+    ].
     ^ (((bH bitShift:8) bitOr:bM) bitShift:8) bitOr:bL
 
     "
@@ -1530,8 +1530,8 @@
     ^ self nextInt64MSB:true
 !
 
-nextNumber:numBytes 
-    "Return the next n bytes as a positive Integer; 
+nextNumber:numBytes
+    "Return the next n bytes as a positive Integer;
      bytes are taken msb-first."
 
     ^ self nextUnsigned:numBytes MSB:true
@@ -1868,9 +1868,9 @@
     "
 !
 
-nextNumber:n put:v 
+nextNumber:n put:v
     "Append to the receiver the argument, v, which is a positive Integer,
-     as the next n bytes. Bytes are written msb first. 
+     as the next n bytes. Bytes are written msb first.
      Possibly pad with leading zeros.
      The receiver must support writing of binary bytes."
 
@@ -1879,8 +1879,8 @@
 
 nextNumber:n put:v MSB:msb
     "Append to the receiver the argument, v, which is a positive Integer,
-     as the next n bytes. 
-     Bytes are written in the specified byte order. 
+     as the next n bytes.
+     Bytes are written in the specified byte order.
      Possibly pad with leading zeros (trailing zeros, if lsb).
      The receiver must support writing of binary bytes."
 
@@ -1904,9 +1904,9 @@
                 bh := (v bitShift:-8) bitAnd:16rFF.
                 msb ifTrue:[
                     self nextPutByte:bh; nextPutByte:bl.
-                ] ifFalse:[    
+                ] ifFalse:[
                     self nextPutByte:bl; nextPutByte:bh.
-                ].    
+                ].
                 ^ self
             ].
         ].
@@ -1923,7 +1923,7 @@
                     self nextPutByte:bl.
                     self nextPutByte:bm.
                     self nextPutByte:bh.
-                ].    
+                ].
                 ^ self
             ].
         ].
@@ -1963,7 +1963,7 @@
         "pad with leading zeros"
         i := n.
         [i > vlen] whileTrue:[
-            self nextPutByte:0. 
+            self nextPutByte:0.
             i := i - 1
         ].
 
@@ -1972,18 +1972,18 @@
         ].
 
         [i > 0] whileTrue:[
-            self nextPutByte:(v digitAt:i). 
+            self nextPutByte:(v digitAt:i).
             i := i - 1
         ]
     ] ifFalse:[
         1 to:vlen do:[:i |
             self nextPutByte:(v digitAt:i).
-        ].    
+        ].
         "pad with trailing zeros"
         vlen+1 to:n do:[:i |
-            self nextPutByte:0. 
+            self nextPutByte:0.
         ].
-    ].    
+    ].
 
     "Modified: / 22-06-2006 / 11:31:13 / fm"
 !
@@ -2034,7 +2034,7 @@
 !
 
 nextPutByte:aByteValue
-    "write a byte. 
+    "write a byte.
      Same as nextPut: here; for protocol compatibility with externalStream."
 
     self nextPut:aByteValue
@@ -2047,10 +2047,10 @@
     "write bytes from an object; the number of bytes is defined by
      the object's size.
      Return the number of bytes written or nil on error.
-     The object must have non-pointer indexed instvars 
-     (i.e. be a ByteArray, String, Float- or DoubleArray).     
+     The object must have non-pointer indexed instvars
+     (i.e. be a ByteArray, String, Float- or DoubleArray).
      Use with care - non object oriented i/o.
-     Warning: in general, you cannot use this method to pass non-byte data to other 
+     Warning: in general, you cannot use this method to pass non-byte data to other
      architectures since it does not care for byte order or float representation."
 
     ^ self nextPutBytes:(anObject size) from:anObject startingAt:1
@@ -2061,10 +2061,10 @@
 nextPutBytes:count from:anObject
     "write count bytes from an object.
      Return the number of bytes written or nil on error.
-     The object must have non-pointer indexed instvars 
-     (i.e. be a ByteArray, String, Float- or DoubleArray).     
+     The object must have non-pointer indexed instvars
+     (i.e. be a ByteArray, String, Float- or DoubleArray).
      Use with care - non object oriented i/o.
-     Warning: in general, you cannot use this method to pass non-byte data to other 
+     Warning: in general, you cannot use this method to pass non-byte data to other
      architectures since it does not care for byte order or float representation."
 
     ^ self nextPutBytes:count from:anObject startingAt:1
@@ -2139,9 +2139,9 @@
 !
 
 nextPutInt16:anIntegerOrCharacter MSB:msbFlag
-    "Write the argument, anIntegerOrCharacter as a short (two bytes). 
-     If msbFlag is true, data is written most-significant byte first; 
-     otherwise least first. 
+    "Write the argument, anIntegerOrCharacter as a short (two bytes).
+     If msbFlag is true, data is written most-significant byte first;
+     otherwise least first.
      Returns the receiver on ok, nil on error.
      The receiver must support writing of binary bytes.
 
@@ -2173,7 +2173,7 @@
 
      s := #[] writeStream.
      s nextPutInt16:16r1234 MSB:false.
-     s contents.  
+     s contents.
     "
     "
      |s|
@@ -2214,9 +2214,9 @@
 !
 
 nextPutInt32:aNumber MSB:msbFlag
-    "Write the argument, aNumber as a long (four bytes). 
-     If msbFlag is true, data is written most-significant byte first; 
-     otherwise least first. 
+    "Write the argument, aNumber as a long (four bytes).
+     If msbFlag is true, data is written most-significant byte first;
+     otherwise least first.
      Returns the receiver on ok, nil on error.
      The receiver must support writing of binary bytes.
 
@@ -2257,7 +2257,7 @@
      s nextPutInt32:16r12345678 MSB:false.
      bytes := s contents.
      s := bytes readStream.
-     (s nextInt32MSB:false) hexPrintString.   
+     (s nextInt32MSB:false) hexPrintString.
     "
     "
      |s bytes|
@@ -2266,7 +2266,7 @@
      s nextPutInt32:16r12345678 MSB:true.
      bytes := s contents.
      s := bytes readStream.
-     (s nextInt32MSB:true) hexPrintString.   
+     (s nextInt32MSB:true) hexPrintString.
 .
     "
     "
@@ -2276,7 +2276,7 @@
      s nextPutInt32:16r-80000000 MSB:true.
      bytes := s contents.
      s := bytes readStream.
-     (s nextInt32MSB:true) hexPrintString.   
+     (s nextInt32MSB:true) hexPrintString.
     "
     "
      |s bytes|
@@ -2285,7 +2285,7 @@
      s nextPutInt32:16r-80000000 MSB:false.
      bytes := s contents.
      s := bytes readStream.
-     (s nextInt32MSB:false) hexPrintString.   
+     (s nextInt32MSB:false) hexPrintString.
     "
 
     "Modified: / 01-11-1997 / 18:30:52 / cg"
@@ -2318,9 +2318,9 @@
 !
 
 nextPutInt64:aNumber MSB:msbFlag
-    "Write the argument, aNumber as a longlong (8 bytes). 
-     If msbFlag is true, data is written most-significant byte first; 
-     otherwise least first. 
+    "Write the argument, aNumber as a longlong (8 bytes).
+     If msbFlag is true, data is written most-significant byte first;
+     otherwise least first.
      Returns the receiver on ok, nil on error.
      The receiver must support writing of binary bytes.
 
@@ -2347,7 +2347,7 @@
      s nextPutInt64:16r123456789abcdef0 MSB:false.
      bytes := s contents.
      s := bytes readStream.
-     (s nextUInt64MSB:false) hexPrintString.   
+     (s nextUInt64MSB:false) hexPrintString.
     "
     "
      |s bytes|
@@ -2356,7 +2356,7 @@
      s nextPutInt64:16r123456789abcdef0 MSB:true.
      bytes := s contents.
      s := bytes readStream.
-     (s nextUInt64MSB:true) hexPrintString.   
+     (s nextUInt64MSB:true) hexPrintString.
     "
     "
      |s bytes|
@@ -2365,7 +2365,7 @@
      s nextPutInt64:16r-8000000000000000 MSB:true.
      bytes := s contents.
      s := bytes readStream.
-     (s nextUInt64MSB:true) hexPrintString.    
+     (s nextUInt64MSB:true) hexPrintString.
     "
     "
      |s bytes|
@@ -2374,7 +2374,7 @@
      s nextPutInt64:16r-8000000000000000 MSB:false.
      bytes := s contents.
      s := bytes readStream.
-     (s nextUInt64MSB:false) hexPrintString.   
+     (s nextUInt64MSB:false) hexPrintString.
     "
 
     "Modified: / 01-11-1997 / 18:30:52 / cg"
@@ -2440,16 +2440,16 @@
     "
 !
 
-nextPutUtf16Bytes:aCharacter MSB:msb 
+nextPutUtf16Bytes:aCharacter MSB:msb
     "append my UTF-16 representation to the argument, aStream.
      UTF-16 can encode only characters with code points between 0 to 16r10FFFF.
      The underlying stream must support writing of bytes."
-    
+
     |codePoint|
 
     codePoint := aCharacter codePoint.
-    (codePoint <= 16rD7FF 
-        or:[ codePoint >= 16rE000 and:[ codePoint <= 16rFFFF ] ]) 
+    (codePoint <= 16rD7FF
+        or:[ codePoint >= 16rE000 and:[ codePoint <= 16rFFFF ] ])
             ifTrue:[ self nextPutInt16:codePoint MSB:msb. ]
             ifFalse:[
                 codePoint <= 16r10FFFF ifTrue:[
@@ -2538,7 +2538,7 @@
     EncodingError raiseWith:aCharacter errorString:'codePoint > 31bit in #nextPutUtf8:'.
 
     "
-      (String streamContents:[:s| 
+      (String streamContents:[:s|
             s nextPutUtf8:$a.
             s nextPutUtf8:$ü.
             s nextPutUtf8: (Character value:16r1fff).
@@ -2547,7 +2547,7 @@
             s nextPutUtf8: (Character value:16r800).
       ])
             asByteArray
-            
+
     "
 ! !
 
@@ -2555,9 +2555,9 @@
 
 nextPutHyper:aNumber MSB:msbFlag
     <resource: #obsolete>
-    "Write the argument, aNumber as a hyper (8 bytes). 
-     If msbFlag is true, data is written most-significant byte first; 
-     otherwise least first. 
+    "Write the argument, aNumber as a hyper (8 bytes).
+     If msbFlag is true, data is written most-significant byte first;
+     otherwise least first.
      Returns the receiver on ok, nil on error.
      The receiver must support writing of binary bytes.
 
@@ -2576,7 +2576,7 @@
      s nextPutHyper:16r123456789abcdef0 MSB:false.
      bytes := s contents.
      s := bytes readStream.
-     (s nextHyperMSB:false) hexPrintString.   
+     (s nextHyperMSB:false) hexPrintString.
     "
     "
      |s bytes|
@@ -2585,7 +2585,7 @@
      s nextPutHyper:16r123456789abcdef0 MSB:true.
      bytes := s contents.
      s := bytes readStream.
-     (s nextHyperMSB:true) hexPrintString.   
+     (s nextHyperMSB:true) hexPrintString.
 .
     "
     "
@@ -2595,7 +2595,7 @@
      s nextPutHyper:16r-8000000000000000 MSB:true.
      bytes := s contents.
      s := bytes readStream.
-     (s nextHyperMSB:true) hexPrintString.    
+     (s nextHyperMSB:true) hexPrintString.
     "
     "
      |s bytes|
@@ -2604,7 +2604,7 @@
      s nextPutHyper:16r-8000000000000000 MSB:false.
      bytes := s contents.
      s := bytes readStream.
-     (s nextHyperMSB:false) hexPrintString.   
+     (s nextHyperMSB:false) hexPrintString.
     "
 
     "Modified: / 01-11-1997 / 18:30:52 / cg"
@@ -2613,9 +2613,9 @@
 
 nextPutLong:aNumber MSB:msbFlag
     <resource: #obsolete>
-    "Write the argument, aNumber as a long (four bytes). 
-     If msbFlag is true, data is written most-significant byte first; 
-     otherwise least first. 
+    "Write the argument, aNumber as a long (four bytes).
+     If msbFlag is true, data is written most-significant byte first;
+     otherwise least first.
      Returns the receiver on ok, nil on error.
      The receiver must support writing of binary bytes.
 
@@ -2634,7 +2634,7 @@
      s nextPutLong:16r12345678 MSB:false.
      bytes := s contents.
      s := bytes readStream.
-     (s nextLongMSB:false) hexPrintString.   
+     (s nextLongMSB:false) hexPrintString.
     "
     "
      |s bytes|
@@ -2643,7 +2643,7 @@
      s nextPutLong:16r12345678 MSB:true.
      bytes := s contents.
      s := bytes readStream.
-     (s nextLongMSB:true) hexPrintString.   
+     (s nextLongMSB:true) hexPrintString.
 .
     "
     "
@@ -2653,7 +2653,7 @@
      s nextPutLong:16r-80000000 MSB:true.
      bytes := s contents.
      s := bytes readStream.
-     (s nextLongMSB:true) hexPrintString.   
+     (s nextLongMSB:true) hexPrintString.
     "
     "
      |s bytes|
@@ -2662,7 +2662,7 @@
      s nextPutLong:16r-80000000 MSB:false.
      bytes := s contents.
      s := bytes readStream.
-     (s nextLongMSB:false) hexPrintString.   
+     (s nextLongMSB:false) hexPrintString.
     "
 
     "Modified: / 01-11-1997 / 18:30:52 / cg"
@@ -2683,9 +2683,9 @@
 
 nextPutShort:anIntegerOrCharacter MSB:msbFlag
     <resource: #obsolete>
-    "Write the argument, anIntegerOrCharacter as a short (two bytes). 
-     If msbFlag is true, data is written most-significant byte first; 
-     otherwise least first. 
+    "Write the argument, anIntegerOrCharacter as a short (two bytes).
+     If msbFlag is true, data is written most-significant byte first;
+     otherwise least first.
      Returns the receiver on ok, nil on error.
      The receiver must support writing of binary bytes.
 
@@ -2702,7 +2702,7 @@
 
      s := #[] writeStream.
      s nextPutShort:16r1234 MSB:false.
-     s contents.  
+     s contents.
     "
     "
      |s|
@@ -2741,8 +2741,8 @@
 contentsSpecies
     "this should return the class of which an instance is
      returned by the #contents method. Here, Array is returned,
-     since the abstract Stream-class has no idea of the underlying 
-     collection class. 
+     since the abstract Stream-class has no idea of the underlying
+     collection class.
      It is redefined in some subclasses - for example, to return String."
 
     ^ Array
@@ -2846,8 +2846,8 @@
 !
 
 numAvailableForRead
-    "answer the nuber of bytes available for reading"
-    
+    "answer the number of bytes available for reading"
+
     ^ self size
 !
 
@@ -2903,7 +2903,7 @@
     "return the next count elements of the stream as aCollection,
      which depends on the streams type - (see #contentsSpecies)."
 
-    |answerStream 
+    |answerStream
      cnt  "{ Class: SmallInteger }" |
 
     cnt := count.
@@ -3008,10 +3008,10 @@
     ^ answerStream contents
 
     "
-     (ReadStream on:#(1 2 3 4 5)) nextAvailable:3 
-     (ReadStream on:#(1 2 3 4 5)) nextAvailable:10 
+     (ReadStream on:#(1 2 3 4 5)) nextAvailable:3
+     (ReadStream on:#(1 2 3 4 5)) nextAvailable:10
      (ReadStream on:'hello') nextAvailable:3
-     (ReadStream on:'hello') nextAvailable:10 
+     (ReadStream on:'hello') nextAvailable:10
     "
 
     "Modified: / 16.6.1998 / 15:52:41 / cg"
@@ -3061,7 +3061,7 @@
     ^ self next
 !
 
-skip:numberToSkip 
+skip:numberToSkip
     "skip numberToSkip objects, return the receiver"
 
     "don't know how to unread ..."
@@ -3082,7 +3082,7 @@
 !
 
 skipFor:anObject
-    "skip all objects up-to and including anObject; 
+    "skip all objects up-to and including anObject;
      read and return the element after anObject."
 
     (self skipThrough:anObject) notNil ifTrue:[
@@ -3093,8 +3093,8 @@
     "
      |s next rest|
      s := ReadStream on:#(1 2 3 4 5 6 7 8).
-     next := s skipFor:4.      
-     rest := s upToEnd.   
+     next := s skipFor:4.
+     rest := s upToEnd.
     "
     "
      |s next rest|
@@ -3115,8 +3115,8 @@
 !
 
 skipThrough:anObject
-    "skip all objects up-to and including anObject. 
-     Return the receiver if skip was successful, 
+    "skip all objects up-to and including anObject.
+     Return the receiver if skip was successful,
      otherwise (i.e. if not found) return nil and leave the stream positioned at the end.
      The next read operation will return the element after anObject."
 
@@ -3141,33 +3141,33 @@
      s := ReadStream on:#(1 2 3 4 5 6 7 8).
      s skipThrough:4.
      s skipThrough:4.
-     s next     
+     s next
     "
     "
      |s|
      s := ReadStream on:'12345678'.
      s skipThrough:$4.
-     s next     
+     s next
     "
     "
      |s|
      s := ReadStream on:'12345678'.
      s skipThrough:$4.
      s skipThrough:$4.
-     s next     
+     s next
     "
     "
      |s|
      s := ReadStream on:'12345678'.
      s skipThrough:$4.
      s skipThrough:$4.
-     s atEnd     
+     s atEnd
     "
 !
 
 skipThroughAll:aCollection
     "skip for and through the sequence given by the argument, aCollection;
-     return nil if not found, the receiver otherwise. 
+     return nil if not found, the receiver otherwise.
      On a successful match, the next read will return elements after aCollection;
      if no match was found, the receiver will be positioned at the end."
 
@@ -3176,18 +3176,18 @@
     l := aCollection size.
     first := aCollection at:1.
     [self atEnd] whileFalse:[
-	buffer isNil ifTrue:[
-	    buffer := self nextAvailable:l.
-	].
-	buffer = aCollection ifTrue:[
-	    ^ self
-	].
-	idx := buffer indexOf:first startingAt:2.
-	idx == 0 ifTrue:[
-	    buffer := nil
-	] ifFalse:[
-	    buffer := (buffer copyFrom:idx) , (self nextAvailable:(idx - 1))
-	]
+        buffer isNil ifTrue:[
+            buffer := self nextAvailable:l.
+        ].
+        buffer = aCollection ifTrue:[
+            ^ self
+        ].
+        idx := buffer indexOf:first startingAt:2.
+        idx == 0 ifTrue:[
+            buffer := nil
+        ] ifFalse:[
+            buffer := (buffer copyFrom:idx) , (self nextAvailable:(idx - 1))
+        ]
     ].
     ^ nil
 
@@ -3195,19 +3195,19 @@
      |s|
      s := ReadStream on:'12345678901234567890'.
      s skipThroughAll:'901'.
-     s upToEnd                    
+     s upToEnd
     "
     "
      |s|
      s := ReadStream on:'12345678901234567890'.
      s skipThroughAll:'1234'.
-     s upToEnd                    
+     s upToEnd
     "
     "
      |s|
      s := ReadStream on:'12345678901234567890'.
      s skipThroughAll:'999'.
-     s atEnd                    
+     s atEnd
     "
 
     "Created: 11.1.1997 / 18:55:13 / cg"
@@ -3215,7 +3215,7 @@
 !
 
 skipUntil:aBlock
-    "skip all elements for which aBlock returns false. 
+    "skip all elements for which aBlock returns false.
      Return true if more elements can be read, false if eof has been reached."
 
     [self atEnd] whileFalse:[
@@ -3252,7 +3252,7 @@
 
 through:anObject
     "read a collection of all objects up-to anObject and return these
-     elements, including anObject. 
+     elements, including anObject.
      The next read operation will return the element after anObject.
      If anObject is not encountered, all elements up to the end are read
      and returned.
@@ -3264,23 +3264,23 @@
 
     answerStream := WriteStream on:(self contentsSpecies new).
     [self atEnd] whileFalse:[
-	element := self next.
-	answerStream nextPut:element.
-	(element = anObject) ifTrue: [
-	    ^ answerStream contents
-	]
+        element := self next.
+        answerStream nextPut:element.
+        (element = anObject) ifTrue: [
+            ^ answerStream contents
+        ]
     ].
     ^ answerStream contents
 
     "
      |s|
      s := ReadStream on:#(1 2 3 4 5 6 7 8).
-     Transcript showCR:(s through:4).  
+     Transcript showCR:(s through:4).
      Transcript showCR:s next
 
      |s|
      s := ReadStream on:#(1 2 3 4 5 6 7 8).
-     Transcript showCR:(s through:9).  
+     Transcript showCR:(s through:9).
      Transcript showCR:s next
 
      |s|
@@ -3293,7 +3293,7 @@
 !
 
 throughAll:aCollection
-    "read & return a collection of all objects up-to and including 
+    "read & return a collection of all objects up-to and including
      a subcollection given by aCollection.
      (i.e. read until a ``substring'' is encountered.)
      The next read operation will return the element after aCollection.
@@ -3305,31 +3305,31 @@
     last := aCollection last.
     answerStream := WriteStream on:(self contentsSpecies new).
     [self atEnd] whileFalse:[
-	element := self next.
-	answerStream nextPut:element.
-	element == last ifTrue:[
-	    ((rslt := answerStream contents) endsWith:aCollection) ifTrue:[
-		^ rslt
-	    ]
-	].
+        element := self next.
+        answerStream nextPut:element.
+        element == last ifTrue:[
+            ((rslt := answerStream contents) endsWith:aCollection) ifTrue:[
+                ^ rslt
+            ]
+        ].
     ].
     ^ answerStream contents
 
     "
      |s|
      s := ReadStream on:#(1 2 3 4 5 6 7 8).
-     Transcript showCR:(s throughAll:#(4 4 4)).  
+     Transcript showCR:(s throughAll:#(4 4 4)).
      Transcript showCR:s next
 
      |s|
      s := ReadStream on:#(1 2 3 4 5 6 7 8).
-     Transcript showCR:(s throughAll:#(4 5 6)).  
+     Transcript showCR:(s throughAll:#(4 5 6)).
      Transcript showCR:s next
 
      |s|
      s := ReadStream on:'hello world, this is some text'.
-     Transcript showCR:(s throughAll:'world').  
-     Transcript showCR:(s throughAll:'some').  
+     Transcript showCR:(s throughAll:'world').
+     Transcript showCR:(s throughAll:'some').
      Transcript showCR:s upToEnd.
     "
 
@@ -3337,7 +3337,7 @@
 !
 
 throughAny:aCollection
-    "read & return a collection of all objects up-to and including 
+    "read & return a collection of all objects up-to and including
      an element contained in aCollection.
      (i.e. read until any from aCollection is encountered.)
      If no such character is encountered, all elements up to the end are read
@@ -3358,13 +3358,13 @@
     "
      |s|
      s := ReadStream on:#(1 2 3 4 5 6 7 8).
-     Transcript showCR:(s throughAny:#(3 4 5)).  
+     Transcript showCR:(s throughAny:#(3 4 5)).
      Transcript showCR:s next
 
      |s|
      s := ReadStream on:'hello world, this is some text'.
-     Transcript showCR:(s throughAny:'wt').  
-     Transcript showCR:(s throughAny:'wt').  
+     Transcript showCR:(s throughAny:'wt').
+     Transcript showCR:(s throughAny:'wt').
      Transcript showCR:s upToEnd.
     "
 
@@ -3397,7 +3397,7 @@
 
 upTo:anObject
     "read a collection of all objects up-to anObject and return these
-     elements, but excluding anObject. 
+     elements, but excluding anObject.
      The next read operation will return the element after anObject.
      (i.e. anObject is considered a separator, which is skipped)
      Similar to #through:, but the matching object is not included in the
@@ -3417,18 +3417,18 @@
     "
      |s|
      s := ReadStream on:#(1 2 3 4 5 6 7 8).
-     Transcript showCR:(s upTo:4).  
+     Transcript showCR:(s upTo:4).
      Transcript showCR:s next
 
      compare the above to:
      |s|
      s := ReadStream on:#(1 2 3 4 5 6 7 8).
-     Transcript showCR:(s through:4).  
+     Transcript showCR:(s through:4).
      Transcript showCR:s next
 
      |s|
      s := ReadStream on:#(1 2 3 4 5 6 7 8).
-     Transcript showCR:(s upTo:9).  
+     Transcript showCR:(s upTo:9).
      Transcript showCR:s next
 
      |s|
@@ -3436,18 +3436,18 @@
      Transcript showCR:(s upTo:Character space).
      Transcript showCR:(s upToEnd)
 
-     (ReadStream on:'12345678905') upTo:$5; next 
-
-     (ReadStream on:'12345678905') upTo:$5; upTo:$5 
-
-     (ReadStream on:'123456') upTo:$7     
-
-     (ReadStream on:#(1 2 3 4 5 6)) upTo:4  
+     (ReadStream on:'12345678905') upTo:$5; next
+
+     (ReadStream on:'12345678905') upTo:$5; upTo:$5
+
+     (ReadStream on:'123456') upTo:$7
+
+     (ReadStream on:#(1 2 3 4 5 6)) upTo:4
 
      (ReadStream on:'line 1
-                     line 2') upTo:Character cr  
-
-     'Makefile' asFilename readStream upTo:Character cr;upTo:Character cr  
+                     line 2') upTo:Character cr
+
+     'Makefile' asFilename readStream upTo:Character cr;upTo:Character cr
     "
 
     "Modified: / 12.1.1998 / 21:58:38 / cg"
@@ -3517,7 +3517,7 @@
 
 upToAny:aCollectionOfObjects
     "read a collection of all objects up-to a element which is contained in
-     aCollectionOfObjects and return these elements, but excluding the matching one. 
+     aCollectionOfObjects and return these elements, but excluding the matching one.
      The next read operation will return the element AFTER anObject.
      If no such element is encountered, all elements up to the end are read
      and returned.
@@ -3539,7 +3539,7 @@
      Transcript showCR:(s upToAny:(Array with:Character space)).
      Transcript showCR:(s upToEnd)
 
-     'Makefile' asFilename readStream upToAny:($A to:$Z)  
+     'Makefile' asFilename readStream upToAny:($A to:$Z)
     "
 
     "Created: / 30.8.1997 / 03:02:05 / cg"
@@ -3548,7 +3548,7 @@
 
 upToBeforeAny:aCollectionOfObjects
     "read a collection of all objects up-to a element which is contained in
-     aCollectionOfObjects and return these elements, but excluding the matching one. 
+     aCollectionOfObjects and return these elements, but excluding the matching one.
      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.
@@ -3574,9 +3574,9 @@
      |s|
      s := ReadStream on:'hello world'.
      Transcript showCR:(s upToBeforeAny:(Array with:Character space)).
-     Transcript showCR:(s upToEnd)    
-
-     'Make.proto' asFilename readStream upToBeforeAny:($A to:$Z)  
+     Transcript showCR:(s upToEnd)
+
+     'Make.proto' asFilename readStream upToBeforeAny:($A to:$Z)
     "
 
     "Created: / 30.8.1997 / 03:02:05 / cg"
@@ -3616,15 +3616,15 @@
 
     answerStream := WriteStream on:(self contentsSpecies new).
     [self atEnd] whileFalse:[
-	answerStream nextPut:(self next)
+        answerStream nextPut:(self next)
     ].
     ^ answerStream contents
 
     "
      (ReadStream on:'1234567890') upToEnd
      ('123456' readStream) next; next; upToEnd
-     ('1 23456' readStream) upTo:Character space; upToEnd 
-     ('12' readStream) next; next; upToEnd  
+     ('1 23456' readStream) upTo:Character space; upToEnd
+     ('12' readStream) next; next; upToEnd
     "
 
     "Modified: 15.5.1996 / 18:00:39 / cg"
@@ -3649,10 +3649,10 @@
 "/    ^ answerStream contents
 
     "
-     'hello world' readStream upToMatching:[:c | c isSeparator].  
+     'hello world' readStream upToMatching:[:c | c isSeparator].
     "
     "
-     'helloworld' readStream upToMatching:[:c | c isSeparator].   
+     'helloworld' readStream upToMatching:[:c | c isSeparator].
     "
     "
      |s|
@@ -3669,21 +3669,21 @@
     "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 
+     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   
+     'hello world' readStream upToSeparator
+     'helloworld' readStream upToSeparator
+     'helloworld' readStream upToSeparator
+     '' readStream upToSeparator
 
      |s|
      s := 'hello world' readStream.
      s upToSeparator.
-     s upToEnd  
+     s upToEnd
     "
 
     "Modified: 4.1.1997 / 23:38:05 / cg"
@@ -3791,7 +3791,7 @@
         answerStream backStep.
     ].
     ^ answerStream contents
-        
+
 
     "Modified: / 19.5.1998 / 17:26:25 / cg"
 ! !
@@ -4086,8 +4086,8 @@
 
     "
      1 to: 10 do:[:i |
-        Transcript 
-            format:'[%1] Hello %2 World - this is %3%<cr>' 
+        Transcript
+            format:'[%1] Hello %2 World - this is %3%<cr>'
             with:{i . 'my' . 'nice'}
      ].
     "
@@ -4148,7 +4148,7 @@
 
     (aCollection notNil and:[aCollection isSequenceable]) ifFalse:[
         "/ fallback
-        aCollection do:[:eachElement|    
+        aCollection do:[:eachElement|
             self nextPut:eachElement.
         ].
          ^ self.
@@ -4169,7 +4169,7 @@
 
      s := WriteStream on:(String new).
      s nextPutAll:($a to:$f).
-     s nextPutAll:'one '; 
+     s nextPutAll:'one ';
        nextPutAll:'two ';
        nextPutAll:'three'.
      s contents
@@ -4183,7 +4183,7 @@
      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 
+     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.
@@ -4212,7 +4212,7 @@
 
      s := WriteStream on:#().
      s nextPutAll:#('one' 'two' 'three' 'four' 'five') startingAt:2.
-     s contents  
+     s contents
     "
 
     "Modified: 11.7.1996 / 10:00:28 / cg"
@@ -4241,7 +4241,7 @@
 
 nextPutAllLines:aCollectionOfStrings
     "put all elements of the argument, aCollection as individual lines
-     onto the receiver, append a cr (carriage return) after each. 
+     onto the receiver, append a cr (carriage return) after each.
      This is only useful with character streams in textMode,
      and only allowed, if the receiver supports writing."
 
@@ -4325,7 +4325,7 @@
 
 printf:format
     "C-style printing into a stream"
-    
+
     format printf:#() on:self.
 
     "
@@ -4335,7 +4335,7 @@
 
 printf:format with:argument
     "C-style printing into a stream"
-    
+
     format printf:{argument} on:self.
 
     "
@@ -4345,7 +4345,7 @@
 
 printf:format with:argument1 with:argument2
     "C-style printing into a stream"
-    
+
     format printf:{argument1 . argument2} on:self.
 
     "
@@ -4355,7 +4355,7 @@
 
 printf:format with:argument1 with:argument2 with:argument3
     "C-style printing into a stream"
-    
+
     format printf:{argument1 . argument2 . argument3} on:self.
 
     "
@@ -4366,7 +4366,7 @@
 
 printf:format with:argument1 with:argument2 with:argument3 with:argument4
     "C-style printing into a stream"
-    
+
     format printf:{argument1 . argument2 . argument3 . argument4} on:self.
 
     "
@@ -4378,7 +4378,7 @@
 
 printf:format with:argument1 with:argument2 with:argument3 with:argument4 with:argument5
     "C-style printing into a stream"
-    
+
     format printf:{argument1 . argument2 . argument3 . argument4 . argument5} on:self.
 
     "
@@ -4390,7 +4390,7 @@
 
 printf:format withAll:arguments
     "C-style printing into a stream"
-    
+
     format printf:arguments on:self.
 
     "
@@ -4416,7 +4416,7 @@
 show:something
     "append a printed representation of the argument to the stream.
      This makes streams somewhat compatible to TextCollectors and
-     allows you to say: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4427,7 +4427,7 @@
     "append a printed representation of the argument to the stream, expanding
      the placeHolder %1 with the printString of arg.
      This makes streams somewhat compatible to TextCollectors and
-     allows you to say: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4440,7 +4440,7 @@
     "append a printed representation of the argument to the stream, expanding
      the placeHolders %1 and %2 with the printStrings of arg1 and arg2.
      This makes streams somewhat compatible to TextCollectors and
-     allows you to say: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4453,7 +4453,7 @@
     "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: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4466,7 +4466,7 @@
     "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: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4479,7 +4479,7 @@
     "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: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4492,7 +4492,7 @@
     "append a printed representation of the argument to the stream, expanding
      the placeHolders %1,%2 and %3 with the printStrings of argi.
      This makes streams somewhat compatible to TextCollectors and
-     allows you to say: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4503,8 +4503,8 @@
     "append a printed representation of the argument to the stream
      and append a newline character.
      This makes streams somewhat compatible to TextCollectors and
-     allows you to say: 
-	Smalltalk at:#Transcript put:Stdout
+     allows you to say:
+        Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
     self show:aString.
@@ -4518,7 +4518,7 @@
     "append a printed representation of the argument to the stream, expanding
      the placeHolder %1 with the printString of arg.
      This makes streams somewhat compatible to TextCollectors and
-     allows you to say: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4531,7 +4531,7 @@
     "append a printed representation of the argument to the stream, expanding
      the placeHolders %1 and %2 with the printStrings of arg1 and arg2.
      This makes streams somewhat compatible to TextCollectors and
-     allows you to say: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4544,7 +4544,7 @@
     "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: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4557,7 +4557,7 @@
     "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: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4570,7 +4570,7 @@
     "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: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4583,7 +4583,7 @@
     "append a printed representation of the argument to the stream, expanding
      the placeHolders %1,%2 and %3 with the printStrings of argi.
      This makes streams somewhat compatible to TextCollectors and
-     allows you to say: 
+     allows you to say:
         Smalltalk at:#Transcript put:Stdout
      or to use #show:/#showCR: with internal or external streams."
 
@@ -4663,7 +4663,7 @@
 
 nextChunkPut:aString
     "put aString as a chunk onto the receiver;
-     double all exclamation marks except within primitives and append a 
+     double all exclamation marks except within primitives and append a
      single delimiting exclamation mark at the end.
      This modification of the chunk format (not doubling exclas in primitive code)
      was done to have primitive code more readable and easier be edited in the fileBrowser
@@ -4704,7 +4704,7 @@
 
     [index <= endIndex] whileTrue:[
         "
-         find position of next interesting character; 
+         find position of next interesting character;
          output stuff up to that one in one piece
         "
         next := aString indexOfAny:stopChars startingAt:index ifAbsent:stop.