Stream.st
branchjv
changeset 20131 4118d61ddba0
parent 20080 093324d7a47c
parent 20102 1ccf35cea466
child 20205 03e626304d06
--- a/Stream.st	Wed Jul 06 06:50:27 2016 +0200
+++ b/Stream.st	Sat Jul 09 21:10:24 2016 +0100
@@ -214,6 +214,7 @@
     ^ ChunkSeparator
 ! !
 
+
 !Stream methodsFor:'Compatibility-Dolphin'!
 
 display:someObject
@@ -223,57 +224,6 @@
     self nextPutAll: someObject asString.
 ! !
 
-!Stream methodsFor:'Compatibility-ST80'!
-
-nextLongPut:aNumber
-    <resource: #obsolete>
-
-    "for ST-80 compatibility:
-     Write the argument, aNumber as a long (four bytes). 
-     The most significant byte is sent first."
-
-    ^ self nextPutInt32:aNumber MSB:true
-
-    "Modified: 10.1.1996 / 19:38:54 / cg"
-!
-
-nextPutWord:aNumber
-    <resource: #obsolete>
-
-    "write the argument, aNumber as a signed short (two bytes);
-     write msb-first for compatibility with other smalltalks.
-     The receiver must support writing of binary bytes.
-     I dont know if it should be named nextPutWord: or nextWordPut:;
-     one of them will vanish ..."
-
-    ^ self nextPutInt16:aNumber MSB:true
-!
-
-nextTwoBytesPut: anInteger
-    <resource: #obsolete>
-    "Write anInteger as the next two bytes of the
-     receiver stream."
-
-    self obsoleteMethodWarning:'use #nextPutShort:MSB:'.
-
-    self
-        nextPutByte: (anInteger bitAnd: 255);
-        nextPutByte: ((anInteger bitShift: -8) bitAnd: 255)
-
-    "Created: / 21-06-2006 / 19:42:10 / fm"
-!
-
-nextWordPut:aNumber
-    <resource: #obsolete>
-
-    "for ST-80 compatibility:
-     Write the argument, aNumber as a short (two bytes). 
-     The most significant byte is sent first."
-
-    ^ self nextPutInt16:aNumber MSB:true
-
-    "Modified: 10.1.1996 / 19:39:19 / cg"
-! !
 
 
 
@@ -1059,20 +1009,6 @@
     ^ ShortFloat readBinaryIEEESingleFrom:self MSB:msbFirst
 !
 
-nextInt16LSB
-    "return a signed short (2 bytes) in LSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextInt16MSB:false
-!
-
-nextInt16MSB
-    "return a signed short (2 bytes) in MSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextInt16MSB:true
-!
-
 nextInt16MSB:msbFlag
     "return a signed short (2 bytes) from the stream.
      The receiver must support reading of binary bytes.
@@ -1108,16 +1044,6 @@
     "Modified: 11.7.1996 / 10:07:04 / cg"
 !
 
-nextInt16Net
-    "return a signed short (2 bytes) in network byte order from the stream.
-     The receiver must support reading of binary bytes.
-     Network byte order is MSB-first per definition"
-
-    ^ self nextInt16MSB:true
-
-    "Created: 10.1.1996 / 19:49:41 / cg"
-!
-
 nextInt24MSB:msbFlag
     "return a signed 3 byte integer from the stream.
      The receiver must support reading of binary bytes.
@@ -1148,20 +1074,6 @@
     "
 !
 
-nextInt32LSB
-    "return a signed long (4 bytes) in LSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextInt32MSB:false
-!
-
-nextInt32MSB
-    "return a signed long (4 bytes) in MSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextInt32MSB:true
-!
-
 nextInt32MSB:msbFlag
     "return a signed long (4 bytes) from the stream.
      The receiver must support reading of binary bytes.
@@ -1224,30 +1136,6 @@
     "Modified: / 14.1.1998 / 15:40:41 / cg"
 !
 
-nextInt32Net
-    "return a signed long (4 bytes) in network byte order from the stream.
-     The receiver must support reading of binary bytes.
-     Network byte order is MSB-first per definition"
-
-    ^ self nextInt32MSB:true
-
-    "Created: 10.1.1996 / 19:49:28 / cg"
-!
-
-nextInt64LSB
-    "return a signed longlong (also called hyper) (8 bytes) in LSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextInt64MSB:false
-!
-
-nextInt64MSB
-    "return a signed longlong (also called hyper) (8 bytes) in MSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextInt64MSB:true
-!
-
 nextInt64MSB:msbFlag
     "return a signed longlong (also called hyper) (8 bytes) from the stream.
      The receiver must support reading of binary bytes.
@@ -1301,21 +1189,6 @@
     "Modified: / 14.1.1998 / 15:40:41 / cg"
 !
 
-nextInt64Net
-    "return a signed longlong (also called hyper) (8 bytes) in network byte order from the stream.
-     The receiver must support reading of binary bytes.
-     Network byte order is MSB-first per definition"
-
-    ^ self nextInt64MSB:true
-!
-
-nextNumber:numBytes 
-    "Return the next n bytes as a positive Integer; 
-     bytes are taken msb-first."
-
-    ^ self nextUnsigned:numBytes MSB:true
-!
-
 nextSignedByte
     "return a signed byte (-128..127) from the stream.
      The receiver must support reading of binary bytes."
@@ -1418,65 +1291,6 @@
     "
 !
 
-nextUnsignedHyperMSB:msbFlag
-    "return an unsigned hyper (8 bytes) from the stream.
-     The receiver must support reading of binary bytes.
-
-     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 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."
-
-    ^ self nextUnsignedInt64MSB:msbFlag
-
-    "
-     |bytes s|
-
-     bytes := #[16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF].
-     s := bytes readStream.
-     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
-     s reset.
-     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.
-
-     bytes := #[16r10 16r00 16r00 16r00 16r00 16r00 16r00 16r00].
-     s := bytes readStream.
-     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
-     s reset.
-     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.
-
-     bytes := #[16r12 16r34 16r56 16r78 16r9a 16rbc 16rde 16rf0].
-     s := bytes readStream.
-     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
-     s reset.
-     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.
-
-     bytes := #[16rFe 16rdc 16rba 16r98 16r76 16r54 16r32 16r10].
-     s := bytes readStream.
-     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
-     s reset.
-     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.
-    "
-
-    "Modified: / 14.1.1998 / 15:40:41 / cg"
-!
-
-nextUnsignedInt16LSB
-    "return an unsigned short (2 bytes) in LSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextUnsignedInt16MSB:false
-!
-
-nextUnsignedInt16MSB
-    "return an unsigned short (2 bytes) in MSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextUnsignedInt16MSB:true
-!
-
 nextUnsignedInt16MSB:msbFlag
     "return an unsigned short (2 bytes) from the stream.
      The receiver must support reading of binary bytes.
@@ -1489,19 +1303,22 @@
      order, please use the corresponding xxxNet methods, which use a standard
      network byte order."
 
-    |b1 b2 bH bL|
+    |b1 b2 uval "{ Class: SmallInteger }"|
 
     b1 := self nextByte.
     b2 := self nextByte.
 
     msbFlag ifTrue:[
-        bH := b1.
-        bL := b2.
+        "most significant first"
+        uval := b1 bitShift:8.
+        uval := uval bitOr:b2.
     ] ifFalse:[
-        bL := b1.
-        bH := b2.
-    ].    
-    ^ (bH bitShift:8) bitOr:bL
+        "least significant first"
+        uval := b2 bitShift:8.
+        uval := uval bitOr:b1.
+    ].
+
+    ^ uval
 
     "
      ((ReadStream on:#[16r10 16r20 16r30]) nextUnsignedInt16MSB:true) hexPrintString
@@ -1511,16 +1328,6 @@
     "Modified: 11.7.1996 / 10:07:20 / cg"
 !
 
-nextUnsignedInt16Net
-    "return an unsigned short (2 bytes) in network byte order from the stream.
-     The receiver must support reading of binary bytes.
-     Network byte order is MSB-first per definition"
-
-    ^ self nextUnsignedInt16MSB:true
-
-    "Created: 10.1.1996 / 19:50:02 / cg"
-!
-
 nextUnsignedInt24MSB:msbFlag
     "return an unsigned 3 byte integer from the stream.
      The receiver must support reading of binary bytes.
@@ -1556,20 +1363,6 @@
     "
 !
 
-nextUnsignedInt32LSB
-    "return an unsigned long (4 bytes) in LSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextUnsignedInt32MSB:false
-!
-
-nextUnsignedInt32MSB
-    "return an unsigned long (4 bytes) in MSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextUnsignedInt32MSB:true
-!
-
 nextUnsignedInt32MSB:msbFlag
     "return an unsigned long (4 bytes) from the stream.
      The receiver must support reading of binary bytes.
@@ -1582,7 +1375,7 @@
      order, please use the corresponding xxxNet methods, which use a standard
      network byte order."
 
-    |b1 b2 b3 b4 val|
+    |b1 b2 b3 b4 uval "{ Class: SmallInteger }" val|
 
     b1 := self nextByte.
     b2 := self nextByte.
@@ -1590,44 +1383,18 @@
     b4 := self nextByte.
 
     msbFlag ifTrue:[
-        val := b1.
-        val := (val bitShift:8) bitOr:b2.
-        val := (val bitShift:8) bitOr:b3.
-        val := (val * 256) + b4.
-        ^ val
+        "most significant first"
+        uval := (b1 bitShift:8) bitOr:b2.
+        uval := (uval bitShift:8) bitOr:b3.
+        val := (uval bitShift:8) bitOr:b4.
+    ] ifFalse:[
+        "least significant first"
+        uval := (b4 bitShift:8) bitOr:b3.
+        uval := (uval bitShift:8) bitOr:b2.
+        val := (uval bitShift:8) bitOr:b1.
     ].
-    val := b4.
-    val := (val bitShift:8) bitOr:b3.
-    val := (val bitShift:8) bitOr:b2.
-    val := (val * 256) + b1.
+
     ^ val
-
-    "Modified: 11.7.1996 / 10:07:13 / cg"
-!
-
-nextUnsignedInt32Net
-    "return an unsigned long (4 bytes) in network byte order from the stream.
-     The receiver must support reading of binary bytes.
-     Network byte order is MSB-first per definition"
-
-    ^ self nextUnsignedInt32MSB:true
-
-    "Created: 10.1.1996 / 19:49:02 / cg"
-    "Modified: 10.1.1996 / 19:49:50 / cg"
-!
-
-nextUnsignedInt64LSB
-    "return an unsigned longlong (also called hyper) (8 bytes) in LSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextUnsignedInt64MSB:false
-!
-
-nextUnsignedInt64MSB
-    "return an unsigned longlong (also called hyper) (8 bytes) in MSB-first order from the stream.
-     The receiver must support reading of binary bytes."
-
-    ^ self nextUnsignedInt64MSB:true
 !
 
 nextUnsignedInt64MSB:msbFlag
@@ -1691,6 +1458,148 @@
     "
 
     "Modified: / 14.1.1998 / 15:40:41 / cg"
+! !
+
+!Stream methodsFor:'non homogenous reading - aliases'!
+
+nextInt16LSB
+    "return a signed short (2 bytes) in LSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextInt16MSB:false
+!
+
+nextInt16MSB
+    "return a signed short (2 bytes) in MSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextInt16MSB:true
+!
+
+nextInt16Net
+    "return a signed short (2 bytes) in network byte order from the stream.
+     The receiver must support reading of binary bytes.
+     Network byte order is MSB-first per definition"
+
+    ^ self nextInt16MSB:true
+
+    "Created: 10.1.1996 / 19:49:41 / cg"
+!
+
+nextInt32LSB
+    "return a signed long (4 bytes) in LSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextInt32MSB:false
+!
+
+nextInt32MSB
+    "return a signed long (4 bytes) in MSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextInt32MSB:true
+!
+
+nextInt32Net
+    "return a signed long (4 bytes) in network byte order from the stream.
+     The receiver must support reading of binary bytes.
+     Network byte order is MSB-first per definition"
+
+    ^ self nextInt32MSB:true
+
+    "Created: 10.1.1996 / 19:49:28 / cg"
+!
+
+nextInt64LSB
+    "return a signed longlong (also called hyper) (8 bytes) in LSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextInt64MSB:false
+!
+
+nextInt64MSB
+    "return a signed longlong (also called hyper) (8 bytes) in MSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextInt64MSB:true
+!
+
+nextInt64Net
+    "return a signed longlong (also called hyper) (8 bytes) in network byte order from the stream.
+     The receiver must support reading of binary bytes.
+     Network byte order is MSB-first per definition"
+
+    ^ self nextInt64MSB:true
+!
+
+nextNumber:numBytes 
+    "Return the next n bytes as a positive Integer; 
+     bytes are taken msb-first."
+
+    ^ self nextUnsigned:numBytes MSB:true
+!
+
+nextUnsignedInt16LSB
+    "return an unsigned short (2 bytes) in LSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextUnsignedInt16MSB:false
+!
+
+nextUnsignedInt16MSB
+    "return an unsigned short (2 bytes) in MSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextUnsignedInt16MSB:true
+!
+
+nextUnsignedInt16Net
+    "return an unsigned short (2 bytes) in network byte order from the stream.
+     The receiver must support reading of binary bytes.
+     Network byte order is MSB-first per definition"
+
+    ^ self nextUnsignedInt16MSB:true
+
+    "Created: 10.1.1996 / 19:50:02 / cg"
+!
+
+nextUnsignedInt32LSB
+    "return an unsigned long (4 bytes) in LSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextUnsignedInt32MSB:false
+!
+
+nextUnsignedInt32MSB
+    "return an unsigned long (4 bytes) in MSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextUnsignedInt32MSB:true
+!
+
+nextUnsignedInt32Net
+    "return an unsigned long (4 bytes) in network byte order from the stream.
+     The receiver must support reading of binary bytes.
+     Network byte order is MSB-first per definition"
+
+    ^ self nextUnsignedInt32MSB:true
+
+    "Created: 10.1.1996 / 19:49:02 / cg"
+    "Modified: 10.1.1996 / 19:49:50 / cg"
+!
+
+nextUnsignedInt64LSB
+    "return an unsigned longlong (also called hyper) (8 bytes) in LSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextUnsignedInt64MSB:false
+!
+
+nextUnsignedInt64MSB
+    "return an unsigned longlong (also called hyper) (8 bytes) in MSB-first order from the stream.
+     The receiver must support reading of binary bytes."
+
+    ^ self nextUnsignedInt64MSB:true
 !
 
 nextUnsignedInt64Net
@@ -1837,6 +1746,52 @@
     "Created: 10.1.1996 / 19:49:41 / cg"
 !
 
+nextUnsignedHyperMSB:msbFlag
+    <resource: #obsolete>
+    "return an unsigned hyper (8 bytes) from the stream.
+     The receiver must support reading of binary bytes.
+
+     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 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."
+
+    ^ self nextUnsignedInt64MSB:msbFlag
+
+    "
+     |bytes s|
+
+     bytes := #[16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF].
+     s := bytes readStream.
+     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
+     s reset.
+     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.
+
+     bytes := #[16r10 16r00 16r00 16r00 16r00 16r00 16r00 16r00].
+     s := bytes readStream.
+     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
+     s reset.
+     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.
+
+     bytes := #[16r12 16r34 16r56 16r78 16r9a 16rbc 16rde 16rf0].
+     s := bytes readStream.
+     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
+     s reset.
+     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.
+
+     bytes := #[16rFe 16rdc 16rba 16r98 16r76 16r54 16r32 16r10].
+     s := bytes readStream.
+     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
+     s reset.
+     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.
+    "
+
+    "Modified: / 14.1.1998 / 15:40:41 / cg"
+!
+
 nextUnsignedLongMSB:msbFlag
     <resource: #obsolete>
     "return an unsigned long (4 bytes) from the stream.
@@ -2058,8 +2013,15 @@
 
     sz := aString size.
     1 to:sz do:[:idx|
-        self nextPutInt16:(aString at:idx) codePoint MSB:msb.
+        self nextPutUtf16Bytes:(aString at:idx) MSB:msb.
     ].
+
+    "
+        (#[] writeStream
+            nextPutAllUtf16Bytes:'BÄxxx' MSB:true;
+            nextPutUtf16:(Character codePoint:16r10CCCC) MSB:true;
+            contents)
+   "
 !
 
 nextPutAllUtf8:aString
@@ -2451,7 +2413,7 @@
      Notice: this writes characters - not bytes.
      The underlying stream must be a stream which can deal with characters,
      eg. OrderedCollectionStream, TwoByteCharacterStream, etc.
-     Also notice, that characters above 16rFFFF are escaped according UTF16 sepcifications."
+     Also notice, that characters above 16rFFFF are escaped according UTF16 specifications."
 
     |codePoint "{Class: SmallInteger}"|
 
@@ -2480,6 +2442,48 @@
     "
 !
 
+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 ] ]) 
+            ifTrue:[ self nextPutInt16:codePoint MSB:msb. ]
+            ifFalse:[
+                codePoint <= 16r10FFFF ifTrue:[
+                    |highBits lowBits|
+
+                    codePoint := codePoint - 16r100000.
+                    highBits := codePoint bitShift:-10.
+                    lowBits := codePoint bitAnd:16r3FF.
+                    self nextPutInt16:highBits + 16rD800 MSB:msb.
+                    self nextPutInt16:lowBits + 16rDC00 MSB:msb.
+                ] ifFalse:[
+                    EncodingError raiseWith:aCharacter
+                        errorString:'Character cannot be encoded as UTF-16'.
+                ]
+            ].
+
+    "
+        (#[] writeStream
+            nextPutUtf16:$B MSB:true;
+            nextPutUtf16:$Ä MSB:true;
+            nextPutUtf16:(Character codePoint:16r10CCCC) MSB:true;
+            contents)
+
+        (FileStream newTemporary
+            nextPutUtf16:$B MSB:false;
+            nextPutUtf16:$Ä MSB:false;
+            nextPutUtf16:(Character codePoint:16r10CCCC) MSB:false;
+            reset;
+            binary;
+            contents)"
+!
+
 nextPutUtf8:aCharacter
     "append my UTF-8 representation to the argument, aStream.
      The underlying stream must be a stream which can deal with characters.
@@ -2843,6 +2847,12 @@
     ^ nil
 !
 
+numAvailableForRead
+    "answer the nuber of bytes available for reading"
+    
+    ^ self size
+!
+
 numberOfTerminalCols
     ^ self lineLength
 !
@@ -3777,9 +3787,9 @@
     self atEnd ifTrue:[
         ^ self pastEndRead
     ].
-    answerStream := WriteStream on:(self contentsSpecies new).
+    answerStream := WriteStream on:(self contentsSpecies uninitializedNew:80).
     self upTo:Character cr into:answerStream.
-    (answerStream size > 0 and:[answerStream last = Character return]) ifTrue:[
+    (answerStream size ~~ 0 and:[answerStream last = Character return]) ifTrue:[
         answerStream backStep.
     ].
     ^ answerStream contents