Merge jv
authorMerge Script
Wed, 17 Feb 2016 07:03:44 +0100
branchjv
changeset 19236 e6403ba50de1
parent 19229 c20beb908660 (current diff)
parent 19235 65951fa81f9a (diff)
child 19238 aaf80a17225f
Merge
CharacterArray.st
Integer.st
ReadStream.st
SequenceableCollection.st
Stream.st
--- a/CharacterArray.st	Tue Feb 16 07:24:34 2016 +0000
+++ b/CharacterArray.st	Wed Feb 17 07:03:44 2016 +0100
@@ -320,6 +320,7 @@
     "Created: 3.8.1997 / 18:16:40 / cg"
 ! !
 
+
 !CharacterArray class methodsFor:'cleanup'!
 
 lowSpaceCleanup
@@ -2761,14 +2762,15 @@
      return a byteArray containing single-, double- or even 4-bytewise values.
      The size of the returned byteArray will be the strings size multiplied by the
      size required for the largest character.
+     Attention: The bytes are in native byte order.
      Caveat: better use utf8Encoded, to get reproducable results"
 
     |bytes sz bytesPerCharacter idx str|
 
     str := self string.
     str ~~ self ifTrue:[
-	"/ for text and other wrappers
-	^ str asByteArray
+        "/ for text and other wrappers
+        ^ str asByteArray
     ].
 
     "/ for real strings, a fallback
@@ -2777,25 +2779,41 @@
     bytes := ByteArray new:(sz * bytesPerCharacter).
     idx := 1.
     self do:[:char |
-	|code|
-
-	code := char codePoint.
-	bytesPerCharacter == 2 ifTrue:[
-	    bytes unsignedShortAt:idx put:code
-	] ifFalse:[
-	    bytesPerCharacter == 4 ifTrue:[
-		bytes unsignedLongAt:idx put:code
-	    ] ifFalse:[
-		bytes at:idx put:code
-	    ].
-	].
-	idx := idx + bytesPerCharacter.
+        |code|
+
+        code := char codePoint.
+        bytesPerCharacter == 2 ifTrue:[
+            bytes unsignedShortAt:idx put:code
+        ] ifFalse:[
+            bytesPerCharacter == 4 ifTrue:[
+                bytes unsignedLongAt:idx put:code
+            ] ifFalse:[
+                bytes at:idx put:code
+            ].
+        ].
+        idx := idx + bytesPerCharacter.
     ].
     ^ bytes
 
     "Created: / 27-07-2011 / 00:56:17 / cg"
 !
 
+asByteArrayMSB:msb
+    "depending on the size of the characters in the receiver,
+     return a byteArray containing single-, double- or even 4-bytewise values.
+     The size of the returned byteArray will be the strings size multiplied by the
+     size required for the largest character.
+     Caveat: better use utf8Encoded, to get reproducable results"
+
+    |ba|
+
+    ba := self asByteArray. "/ native order
+    UninterpretedBytes isBigEndian ~~ msb ifTrue:[
+        ba swapBytes
+    ].
+    ^ ba
+!
+
 asCollectionOfLines
     "return a collection containing the lines (separated by cr)
      of the receiver. If multiple cr's occur in a row, the result will
@@ -4435,6 +4453,8 @@
 ! !
 
 
+
+
 !CharacterArray methodsFor:'matching - glob expressions'!
 
 compoundMatch:aString
@@ -7615,6 +7635,7 @@
     ^ aVisitor visitString:self with:aParameter
 ! !
 
+
 !CharacterArray class methodsFor:'documentation'!
 
 version
--- a/Integer.st	Tue Feb 16 07:24:34 2016 +0000
+++ b/Integer.st	Wed Feb 17 07:03:44 2016 +0100
@@ -752,6 +752,8 @@
     "Modified: / 15.11.1999 / 20:35:20 / cg"
 ! !
 
+
+
 !Integer class methodsFor:'class initialization'!
 
 initialize
@@ -797,6 +799,7 @@
     "Modified: 18.7.1996 / 12:26:38 / cg"
 ! !
 
+
 !Integer class methodsFor:'prime numbers'!
 
 flushPrimeCache
@@ -1008,7 +1011,15 @@
 primesUpTo: max
     "Return a list of prime integers up to and including the given integer."
 
-    ^ Array streamContents:[:s| self primesUpTo: max do:[:prime| s nextPut: prime]]
+    |cls|
+
+    max < IntegerArray maxVal ifTrue:[
+        cls := IntegerArray.
+    ] ifFalse:[
+        cls := Array.
+    ].
+
+    ^ cls streamContents:[:s| self primesUpTo: max do:[:prime| s nextPut: prime]]
 
     "
      Integer primesUpTo: 100
@@ -1164,6 +1175,7 @@
     ^ self == Integer
 ! !
 
+
 !Integer methodsFor:'*Roe'!
 
 acceptRoeVisitor: aVisitor
@@ -1434,6 +1446,7 @@
     "
 ! !
 
+
 !Integer methodsFor:'bcd conversion'!
 
 decodeFromBCD
@@ -3517,19 +3530,18 @@
      Where an integer is one bit longer than self.
      This is a helper for modulu numbers"
 
-    |b rem result|
+    |b "{Class: SmallInteger}" rem result digitBytes|
 
     b := self highBit.
     rem := 1 bitShift:b.
     result := LargeInteger basicNew numberOfDigits:(b // 8)+1.
-    b := b+1.
-    [b > 0] whileTrue:[
+    digitBytes := result digitBytes.
+    b+1 to:1 by:-1 do:[:idx|
         rem >= self ifTrue:[
-            rem := rem -= self.
-            result digitBytes bitSetAt:b.
+            rem := rem - self.
+            digitBytes bitSetAt:idx.
         ].
         rem := rem mul2.
-        b := b - 1.
     ].
     ^ result compressed.
 
@@ -3945,25 +3957,17 @@
 
     "now p2 is in result, q2 in t"
 
-    t := t -= result.
-    t < 0 ifTrue:[
+    t := t - result.
+    t negative ifTrue:[
         t := t + q.
     ].
-    t := t *= u.
+    t := t * u.
     t := mq modulusOf:t.
-    t := t *= p.
-    result := result += t.
+    t := t * p.
+    result := result + t.
 
     ^ result.
 
-
-
-    "
-     2 raisedTo:2 mod:3
-      20000000000000 raisedTo:200 mod:190
-     (20000000000000 raisedTo:200) \\ 190
-    "
-
     "Created: / 30.4.1999 / 15:53:15 / stefan"
     "Modified: / 5.5.1999 / 11:01:15 / stefan"
 ! !
@@ -4806,6 +4810,7 @@
     "Created: / 09-01-2012 / 17:18:06 / cg"
 ! !
 
+
 !Integer methodsFor:'special modulo arithmetic'!
 
 add_32:anInteger
@@ -5460,7 +5465,7 @@
 
 modulusOf:dividend
     "compute the aNumber modulo myself.
-     The shortcut works only, if aNumber is < modulo * modulo
+     The shortcut works only, if dividend is < modulo * modulo
      (When doing arithmethic modulo something).
      Otherwise do it the long way"
 
@@ -5473,14 +5478,12 @@
         abs := dividend.
     ].
 
-"/    self assert:aNumber < (modulus * modulus)
+"/    self assert:dividend < (modulus * modulus)
 
     "throw off low nbits(modulus)"
 
-    e := abs bitShift:shift.
-    e := e * reciprocal.
-    e := e bitShift:shift.
-    e := e * modulus.
+    e := (abs bitShift:shift) * reciprocal.
+    e := (e bitShift:shift) * modulus.
     e := abs - e.
 
     "this subtract is done max 2 times"
@@ -5527,8 +5530,13 @@
      |m|
 
      m := self new modulus:123456789901398721398721931729371293712943794254034548369328469438562948623498659238469234659823469823658423659823658.
-    m modulusOf:874928459437598375937451931729371293712943794254034548369328469438562948623498659238469234659823469823658423659823658.
-10730930127807326146398409623772237722337234475792709784029183368622308259008044569184592041059181058049458041058052     ]
+     Time millisecondsToRun:[
+        100000 timesRepeat:[
+            m modulusOf:874928459437598375937451931729371293712943794254034548369328469438562948623498659238469234659823469823658423659823658.
+        ]
+    ].
+
+10730930127807326146398409623772237722337234475792709784029183368622308259008044569184592041059181058049458041058052 
     "
 
     "Modified: / 3.5.1999 / 14:30:32 / stefan"
--- a/ReadStream.st	Tue Feb 16 07:24:34 2016 +0000
+++ b/ReadStream.st	Wed Feb 17 07:03:44 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -584,6 +582,26 @@
     ^ collection at:(position + 1)
 !
 
+nextUnicode16CharacterMSB:msb
+    ^ Character value:(self nextUnsignedShortMSB:msb)
+
+    "
+     #[16r00 16r51] readStream nextUnicode16CharacterMSB:true
+     #[16r00 16r51] readStream nextUnicode16CharacterMSB:false
+    "
+!
+
+nextUnicode16Characters:count MSB:msb
+    ^ (1 to:count) 
+        collect:[:i | self nextUnicode16CharacterMSB:msb]
+        as:Unicode16String
+
+    "
+     #[16r00 16r51] readStream nextUnicode16Characters:1 MSB:true
+     #[16r00 16r51] readStream nextUnicode16Characters:1 MSB:false
+    "
+!
+
 peek
     "return the next element; do NOT advance read pointer.
      return nil, if there is no next element.
@@ -917,10 +935,10 @@
 !ReadStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ReadStream.st,v 1.83 2015-04-22 16:05:16 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/ReadStream.st,v 1.83 2015-04-22 16:05:16 stefan Exp $'
+    ^ '$Header$'
 ! !
 
--- a/SequenceableCollection.st	Tue Feb 16 07:24:34 2016 +0000
+++ b/SequenceableCollection.st	Wed Feb 17 07:03:44 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -398,7 +400,6 @@
     ^ self == SequenceableCollection
 ! !
 
-
 !SequenceableCollection methodsFor:'Compatibility-Squeak'!
 
 allButFirst
@@ -711,7 +712,6 @@
     ^ self replaceFrom:start to:stop with:anArray startingAt:repStart
 ! !
 
-
 !SequenceableCollection methodsFor:'accessing'!
 
 after:anObject
@@ -7765,7 +7765,6 @@
     "Created: 14.2.1997 / 16:13:03 / cg"
 ! !
 
-
 !SequenceableCollection methodsFor:'searching'!
 
 detect:aBlock startingAt:startIndex
--- a/Stream.st	Tue Feb 16 07:24:34 2016 +0000
+++ b/Stream.st	Wed Feb 17 07:03:44 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -275,8 +277,6 @@
     "Modified: 10.1.1996 / 19:39:19 / cg"
 ! !
 
-
-
 !Stream methodsFor:'accessing'!
 
 contents
@@ -2048,7 +2048,7 @@
      |s bytes|
 
      s := #[] writeStream.
-     s nextPutUInt64:16r123456789abcdef0 MSB:false.
+     s nextPutInt64:16r123456789abcdef0 MSB:false.
      bytes := s contents.
      s := bytes readStream.
      (s nextUInt64MSB:false) hexPrintString.   
@@ -2057,7 +2057,7 @@
      |s bytes|
 
      s := #[] writeStream.
-     s nextPutUInt64:16r123456789abcdef0 MSB:true.
+     s nextPutInt64:16r123456789abcdef0 MSB:true.
      bytes := s contents.
      s := bytes readStream.
      (s nextUInt64MSB:true) hexPrintString.   
@@ -2066,7 +2066,7 @@
      |s bytes|
 
      s := #[] writeStream.
-     s nextPutUInt64:16r-8000000000000000 MSB:true.
+     s nextPutInt64:16r-8000000000000000 MSB:true.
      bytes := s contents.
      s := bytes readStream.
      (s nextUInt64MSB:true) hexPrintString.    
@@ -2075,7 +2075,7 @@
      |s bytes|
 
      s := #[] writeStream.
-     s nextPutUInt64:16r-8000000000000000 MSB:false.
+     s nextPutInt64:16r-8000000000000000 MSB:false.
      bytes := s contents.
      s := bytes readStream.
      (s nextUInt64MSB:false) hexPrintString.   
@@ -2093,70 +2093,6 @@
     ^ self nextPutInt64:aNumber MSB:true
 !
 
-nextPutUInt64:aNumber MSB:msbFlag
-    "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.
-
-     This interface is provided to allow talking to external programs,
-     where its 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."
-
-    msbFlag ifTrue:[
-        1 to:8 do:[:i |
-            self nextPutByte:(aNumber digitByteAt:8+1-i)
-        ].
-    ] ifFalse:[
-        1 to:8 do:[:i |
-            self nextPutByte:(aNumber digitByteAt:i)
-        ].
-    ].
-
-    "
-     |s bytes|
-
-     s := #[] writeStream.
-     s nextPutUInt64:16r123456789abcdef0 MSB:false.
-     bytes := s contents.
-     s := bytes readStream.
-     (s nextUInt64MSB:false) hexPrintString.   
-    "
-    "
-     |s bytes|
-
-     s := #[] writeStream.
-     s nextPutUInt64:16r123456789abcdef0 MSB:true.
-     bytes := s contents.
-     s := bytes readStream.
-     (s nextUInt64MSB:true) hexPrintString.   
-    "
-    "
-     |s bytes|
-
-     s := #[] writeStream.
-     s nextPutUInt64:16r-8000000000000000 MSB:true.
-     bytes := s contents.
-     s := bytes readStream.
-     (s nextUInt64MSB:true) hexPrintString.    
-    "
-    "
-     |s bytes|
-
-     s := #[] writeStream.
-     s nextPutUInt64:16r-8000000000000000 MSB:false.
-     bytes := s contents.
-     s := bytes readStream.
-     (s nextUInt64MSB:false) hexPrintString.   
-    "
-
-    "Modified: / 01-11-1997 / 18:30:52 / cg"
-    "Modified: / 22-06-2006 / 11:31:37 / fm"
-!
-
 nextPutUtf16:aCharacter
     "append my UTF-16 representation to the argument, aStream.
      UTF-16 can encode only characters with code points between 0 to 16r10FFFF.
@@ -2183,7 +2119,7 @@
     "
         ((WriteStream on:Unicode16String new)
             nextPutUtf16:$B;
-            nextPutUtf16:$Ä; 
+            nextPutUtf16:$Ä; 
             nextPutUtf16:(Character codePoint:16r10CCCC)
             yourself) contents
     "
@@ -2246,7 +2182,7 @@
     "
       (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).