Number.st
branchjv
changeset 25426 963f86568b2d
parent 21242 19fabe339f8b
--- a/Number.st	Tue Jun 08 22:22:11 2021 +0100
+++ b/Number.st	Tue Jun 08 22:24:38 2021 +0100
@@ -64,6 +64,18 @@
 
 !Number class methodsFor:'instance creation'!
 
+coerce:aNumber
+    "convert the argument aNumber into an instance of the receiver (class) and return it."
+
+    self == Number ifTrue:[
+        self assert:(aNumber isNumber).
+        ^ aNumber
+    ].
+    ^ super coerce:aNumber
+
+    "Created: / 21-06-2017 / 08:58:38 / cg"
+!
+
 fastFromString:aString
     "return the next Float, Integer or ShortFloat from the string.
      No spaces are skipped.
@@ -100,6 +112,53 @@
     "
 !
 
+fastFromString:aString at:startIndex
+    "return the next Float, Integer or ShortFloat from the string.
+     No spaces are skipped.
+
+     This is a specially tuned entry (using a low-level C-call), which
+     returns garbage if the argument string is not a valid float number.
+     It has been added to allow high speed string decomposition into numbers,
+     especially for mass-data."
+
+    self subclassResponsibility
+
+    "
+     Float fromString:'12345.0'
+     Float fastFromString:'12345.0'
+
+     Integer fromString:'12345'
+     Integer fastFromString:'12345'
+
+     should be roughly 10times faster than the general method:
+
+     Time millisecondsToRun:[
+        100000 timesRepeat:[ Float fromString:'12345.0' ]
+     ].
+     Time millisecondsToRun:[
+        100000 timesRepeat:[ Float fastFromString:'12345.0' ]
+     ].
+
+     Time millisecondsToRun:[
+        100000 timesRepeat:[ Integer fromString:'12345' ]
+     ].
+     Time millisecondsToRun:[
+        100000 timesRepeat:[ Integer fastFromString:'12345' ]
+     ].
+    "
+
+    "Created: / 21-07-2019 / 19:17:17 / Claus Gittinger"
+!
+
+fromNumber:aNumber
+    "return aNumber coerced to myself"
+
+    self isAbstract ifTrue:[^ aNumber]. 
+    ^ self coerce:aNumber
+
+    "Created: / 21-06-2017 / 08:57:00 / cg"
+!
+
 fromString:aString
     "return a number by reading from aString.
      In contrast to readFrom:, no garbage is allowed after the number.
@@ -125,6 +184,72 @@
     "Modified: / 3.8.1998 / 20:05:11 / cg"
 !
 
+fromString:aString decimalPointCharacter:decimalPointCharacter
+    "return a number by reading from aString.
+     In contrast to readFrom:, no garbage is allowed after the number.
+     I.e. the string must contain exactly one valid number (with optional separators around)"
+
+    ^ self fromString:aString decimalPointCharacters:(decimalPointCharacter asString)
+
+    "
+     Number fromString:'12345.99' decimalPointCharacter:$.
+     Number fromString:'12345,99' decimalPointCharacter:$,
+    "
+
+    "Created: / 21-07-2019 / 13:09:13 / Claus Gittinger"
+    "Modified (comment): / 21-07-2019 / 18:04:30 / Claus Gittinger"
+!
+
+fromString:aString decimalPointCharacter:decimalPointCharacter onError:exceptionBlock
+    "return a number by reading from aString.
+     In contrast to readFrom:, no garbage is allowed after the number.
+     I.e. the string must contain exactly one valid number (with optional separators around)"
+
+    ^ self 
+        fromString:aString 
+        decimalPointCharacters:(decimalPointCharacter asString) 
+        onError:exceptionBlock.
+
+    "
+     Number fromString:'12,345' decimalPointCharacter:',' onError:0
+     Number fromString:'12,345' decimalPointCharacter:$, onError:0
+     Number fromString:'12,345,456' decimalPointCharacter:$. thouseandsSeparator:$, onError:0
+     Number fromString:'12,345,45' decimalPointCharacter:$. thouseandsSeparator:$, onError:0
+    "
+
+    "Created: / 21-07-2019 / 13:07:39 / Claus Gittinger"
+    "Modified (comment): / 21-07-2019 / 18:50:18 / Claus Gittinger"
+!
+
+fromString:aString decimalPointCharacter:decimalPointCharacter thousandsSeparator:thousandsSeparator onError:exceptionBlock
+    "return a number by reading from aString.
+     In contrast to readFrom:, no garbage is allowed after the number.
+     I.e. the string must contain exactly one valid number (with optional separators around)"
+
+    ^ self 
+        fromString:aString 
+        decimalPointCharacters:(decimalPointCharacter asString) 
+        thousandsSeparator:thousandsSeparator
+        onError:exceptionBlock.
+
+    "
+     Number fromString:'12,345' decimalPointCharacter:',' onError:0
+     Number fromString:'12,345' decimalPointCharacter:$, onError:0
+     Number fromString:'12345,456' decimalPointCharacter:$. thousandsSeparator:$, onError:0
+     Number fromString:'12,345,456' decimalPointCharacter:$. thousandsSeparator:$, onError:0
+     Number fromString:'12,345,456,789' decimalPointCharacter:$. thousandsSeparator:$, onError:0
+     Number fromString:'12,345,456,789.89' decimalPointCharacter:$. thousandsSeparator:$, onError:0
+     Number fromString:'12.345.456.789,89' decimalPointCharacter:$, thousandsSeparator:$. onError:0
+
+    these report an error:
+     Number fromString:'12,345,45' decimalPointCharacter:$. thousandsSeparator:$, onError:0
+     Number fromString:'12.345.456.789' decimalPointCharacter:$. thousandsSeparator:$, onError:0
+     Number fromString:'12.345.456.78' decimalPointCharacter:$. thousandsSeparator:$, onError:0
+    "
+
+    "Created: / 21-07-2019 / 18:50:57 / Claus Gittinger"
+!
+
 fromString:aString decimalPointCharacters:decimalPointCharacters
     "return a number by reading from aString.
      In contrast to readFrom:, no garbage is allowed after the number.
@@ -133,12 +258,15 @@
     |s num|
 
     s := aString readStream.
-    num := self readFrom:s decimalPointCharacters:decimalPointCharacters onError:[^ ConversionError raiseRequestErrorString:' - invalid number'].
+    num := self 
+            readFrom:s 
+            decimalPointCharacters:decimalPointCharacters 
+            onError:[^ ConversionError raiseRequestErrorString:' - invalid number'].
     s atEnd ifFalse:[
-	s skipSeparators.
-	s atEnd ifFalse:[
-	    ^ ConversionError raiseRequestErrorString:' - garbage at end of number'
-	].
+        s skipSeparators.
+        s atEnd ifFalse:[
+            ^ ConversionError raiseRequestErrorString:' - garbage at end of number'
+        ].
     ].
     ^ num.
 
@@ -149,7 +277,8 @@
      '12345' asNumber
     "
 
-    "Modified: / 3.8.1998 / 20:05:11 / cg"
+    "Modified: / 03-08-1998 / 20:05:11 / cg"
+    "Modified (format): / 21-07-2019 / 18:04:58 / Claus Gittinger"
 !
 
 fromString:aString decimalPointCharacters:decimalPointCharacters onError:exceptionBlock
@@ -157,10 +286,37 @@
      In contrast to readFrom:, no garbage is allowed after the number.
      I.e. the string must contain exactly one valid number (with optional separators around)"
 
+    ^ self
+        fromString:aString 
+        decimalPointCharacters:decimalPointCharacters 
+        thousandsSeparator:nil 
+        onError:exceptionBlock
+
+    "
+     Number fromString:'12345' onError:0
+     Number fromString:'12,345' decimalPointCharacters:',' onError:0
+     Number fromString:'12,345' decimalPointCharacters:',' onError:0
+     Number fromString:'fooBarBaz' onError:0
+     Number fromString:'123fooBarBaz' onError:0
+     Number fromString:'123,fooBarBaz' decimalPointCharacters:',' onError:0
+    "
+
+    "Modified: / 03-08-1998 / 20:05:34 / cg"
+    "Modified: / 21-07-2019 / 18:02:55 / Claus Gittinger"
+!
+
+fromString:aString decimalPointCharacters:decimalPointCharacters thousandsSeparator:thousandsSeparator onError:exceptionBlock
+    "return a number by reading from aString.
+     In contrast to readFrom:, no garbage is allowed after the number.
+     I.e. the string must contain exactly one valid number (with optional separators around)"
+
     |s num|
 
     s := aString readStream.
-    num := self readFrom:s decimalPointCharacters:decimalPointCharacters onError:[^ exceptionBlock value].
+    num := self readFrom:s 
+            decimalPointCharacters:decimalPointCharacters 
+            thousandsSeparator:thousandsSeparator
+            onError:[^ exceptionBlock value].
     s atEnd ifFalse:[
         s skipSeparators.
         s atEnd ifFalse:[
@@ -178,7 +334,7 @@
      Number fromString:'123,fooBarBaz' decimalPointCharacters:',' onError:0
     "
 
-    "Modified: / 3.8.1998 / 20:05:34 / cg"
+    "Created: / 21-07-2019 / 18:02:32 / Claus Gittinger"
 !
 
 fromString:aString onError:exceptionBlock
@@ -197,6 +353,54 @@
     "Modified: / 3.8.1998 / 20:05:34 / cg"
 !
 
+readFrom:aStringOrStream decimalPointCharacter:decimalPointCharacter
+    "return the next Number from the (character-)stream aStream;
+     skipping all whitespace first.
+     Return the value of exceptionBlock, if no number can be read.
+     This method is less strict than the smalltalk number reader; it
+     allows for prefixed + and also allows missing fractional part after eE.
+     It also allows garbage after the number - i.e. it reads what it can.
+     See #fromString: , which is more strict and does not allow garbage at the end."
+
+    ^ self
+        readFrom:aStringOrStream
+        decimalPointCharacters:(decimalPointCharacter asString)
+
+    "
+     Number readFrom:'0' decimalPointCharacter:$.  
+     Number readFrom:'123.456' decimalPointCharacter:$.
+     Number readFrom:'123,456' decimalPointCharacter:$,
+    "
+
+    "Created: / 21-07-2019 / 13:09:52 / Claus Gittinger"
+    "Modified (comment): / 17-12-2019 / 14:42:47 / Stefan Reise"
+!
+
+readFrom:aStringOrStream decimalPointCharacter:decimalPointCharacter onError:exceptionBlock
+    "return the next Number from the (character-)stream aStream;
+     skipping all whitespace first.
+     Return the value of exceptionBlock, if no number can be read.
+     This method is less strict than the Smalltalk number reader; 
+     it allows for prefixed + and also allows missing fractional part after eE.
+     It supports the regular Smalltalk radix prefix xr.
+     It also allows garbage after the number - i.e. it reads what it can.
+     See #fromString: , which is more strict and does not allow garbage at the end.
+
+     Notice (see examples below): 
+        if sent to Number, it will decide which type of number to return (depending on the exponent character);
+        if sent to a concrete number-class, an instance of that class will be returned (independent of the exponent character)
+    "
+
+    ^ self readFrom:aStringOrStream decimalPointCharacters:(decimalPointCharacter asString) onError:exceptionBlock
+
+    "
+     Number readFrom:(ReadStream on:'54.32e-01') decimalPointCharacter:$. onError:[self halt].
+     Number readFrom:(ReadStream on:'54,32e-01') decimalPointCharacter:$, onError:[self halt].
+    "
+
+    "Created: / 21-07-2019 / 13:11:12 / Claus Gittinger"
+!
+
 readFrom:aStringOrStream decimalPointCharacters:decimalPointCharacters
     "return the next Number from the (character-)stream aStream;
      skipping all whitespace first.
@@ -218,156 +422,85 @@
     "
 !
 
+readFrom:aStringOrStream decimalPointCharacters:decimalPointCharacters allowCStyle:allowCStyle onError:exceptionBlock
+    "return the next Number from the (character-)stream aStream;
+     skipping all whitespace first.
+     Return the value of exceptionBlock, if no number can be read.
+     This method is less strict than the Smalltalk number reader; 
+     it allows for prefixed + and also allows missing fractional part after eE.
+     It supports 0x, 0o and 0b prefixes (hex, octal and binary)
+     and the regular Smalltalk radix prefix xr.
+     If also allows for strings like '1.0×1015' to be read (as 1E+15).
+
+     It also allows garbage after the number - i.e. it reads what it can.
+     See #fromString: , which is more strict and does not allow garbage at the end.
+
+     Notice (see examples below): 
+        if sent to Number, it will decide which type of number to return (depending on the exponent character);
+        if sent to a concrete number-class, an instance of that class will be returned (independent of the exponent character)
+    "
+
+    ^ self
+        readFrom:aStringOrStream 
+        decimalPointCharacters:decimalPointCharacters
+        thousandsSeparator:nil
+        allowCStyle:allowCStyle onError:exceptionBlock
+
+    "
+     Number readFrom:(ReadStream on:'1.234.567,99') 
+        decimalPointCharacter:$,
+        thousandsSeparator:$.
+        onError:[self halt].
+    "
+
+    "Created: / 27-10-2018 / 09:21:11 / Claus Gittinger"
+    "Modified: / 21-07-2019 / 13:06:54 / Claus Gittinger"
+!
+
 readFrom:aStringOrStream decimalPointCharacters:decimalPointCharacters onError:exceptionBlock
     "return the next Number from the (character-)stream aStream;
      skipping all whitespace first.
      Return the value of exceptionBlock, if no number can be read.
-     This method is less strict than the smalltalk number reader; it
-     allows for prefixed + and also allows missing fractional part after eE.
+     This method is less strict than the Smalltalk number reader; 
+     it allows for prefixed + and also allows missing fractional part after eE.
+     It supports the regular Smalltalk radix prefix xr.
      It also allows garbage after the number - i.e. it reads what it can.
-     See #fromString: , which is more strict and does not allow garbage at the end."
-
-    ^ [
-	|value intValue mantissaAndScale scale decimalMantissa str
-	 nextChar radix sign signExp exp numerator denom|
-
-	str := aStringOrStream readStream.
-
-	nextChar := str skipSeparators.
-	nextChar isNil ifTrue:[^ exceptionBlock value].
-
-	(nextChar == $-) ifTrue:[
-	    sign := -1.
-	    str next.
-	    nextChar := str peekOrNil
-	] ifFalse:[
-	    sign := 1.
-	    (nextChar == $+) ifTrue:[
-		str next.
-		nextChar := str peekOrNil
-	    ]
-	].
-	nextChar == $( ifTrue:[
-	    "maybe a Fraction e.g. (1/3)"
-	    str next.
-	    numerator := Integer readFrom:str onError:[^ exceptionBlock value].
-	    str skipSeparators.
-	    nextChar := str peekOrNil.
-	    nextChar == $/ ifTrue:[
-		str next.
-		denom := Integer readFrom:str onError:[^ exceptionBlock value].
-		str skipSeparators.
-		nextChar := str peekOrNil.
-	    ].
-	    nextChar == $) ifFalse:[^ exceptionBlock value].
-	    str next.
-	    value := Fraction numerator:numerator denominator:denom.
-	    ^ value * sign
-	].
-	nextChar isNil ifTrue:[^ exceptionBlock value].
-	(nextChar isDigit or:[(decimalPointCharacters includes:nextChar)]) ifFalse:[
-	    ^ exceptionBlock value.
-"/          value := super readFrom:str.
-"/          sign == -1 ifTrue:[value := value negated].
-"/          ^ value
-	].
-	(decimalPointCharacters includes:nextChar) ifTrue:[
-	    radix := 10.
-	    value := 0.0.
-	    intValue := 0.
-	] ifFalse:[
-	    value := Integer readFrom:str radix:10.
-	    nextChar := str peekOrNil.
-	    ((nextChar == $r) or:[ nextChar == $R]) ifTrue:[
-		str next.
-		radix := value.
-		value := Integer readFrom:str radix:radix.
-	    ] ifFalse:[
-		radix := 10
-	    ].
-	    intValue := value.
-	].
-
-	(self == Integer or:[self inheritsFrom:Integer]) ifFalse:[
-	    (decimalPointCharacters includes:nextChar) ifTrue:[
-		str next.
-		nextChar := str peekOrNil.
-		decimalMantissa := 0.
-		(nextChar notNil and:[nextChar isDigitRadix:radix]) ifTrue:[
-		    |mantissa|
-		    mantissaAndScale := self readMantissaAndScaleFrom:str radix:radix.
-		    mantissa := mantissaAndScale first.
-		    value := (mantissa coerce:value) + mantissa.
-		    nextChar := str peekOrNil.
-		]
-	    ].
-	    ('eEdDqQ' includes:nextChar) ifTrue:[
-		str next.
-		nextChar := str peekOrNil.
-		signExp := 1.
-		(nextChar == $+) ifTrue:[
-		    str next.
-		    nextChar := str peekOrNil.
-		] ifFalse:[
-		    (nextChar == $-) ifTrue:[
-			str next.
-			nextChar := str peekOrNil.
-			signExp := -1
-		    ]
-		].
-		('qQ' includes:nextChar) ifTrue:[
-		    value := value asLongFloat.
-		] ifFalse:[
-		    value := value asFloat.
-"/ future: (for now, always create Doubles for Dolphin,Squeak etc. compatibility)
-"/                ('eE' includes:nextChar) ifTrue:[
-"/                    value := value asShortFloat
-"/                ]
-		].
-		(nextChar notNil and:[(nextChar isDigitRadix:radix)]) ifTrue:[
-		    exp := (Integer readFrom:str radix:radix) * signExp.
-		    value := value * ((value class unity * 10.0) raisedToInteger:exp)
-		]
-	    ] ifFalse:[
-		('sS' includes:nextChar) ifTrue:[
-		    str next.
-
-		    nextChar := str peekOrNil.
-		    (nextChar notNil and:[ nextChar isDigit]) ifTrue:[
-			scale := (Integer readFrom:str).
-		    ].
-
-		    mantissaAndScale isNil ifTrue:[
-			value := intValue asFixedPoint:(scale ? 0).
-		    ] ifFalse:[
-			denom := 10 raisedTo:mantissaAndScale last.
-			value := FixedPoint
-				    numerator:(intValue * denom) + (mantissaAndScale second)
-				    denominator:denom
-				    scale:(scale ? mantissaAndScale third).
-		    ].
-		] ifFalse:[
-		    (self inheritsFrom:LimitedPrecisionReal) ifTrue:[
-			"when requesting a specific Float instance, coerce it.
-			 otherwise return a value without loosing precision"
-			value := self coerce:value.
-		    ].
-		].
-	    ].
-	].
-	sign == -1 ifTrue:[
-	    value := value negated
-	].
-	value.
-    ] on:Error do:exceptionBlock
+     See #fromString: , which is more strict and does not allow garbage at the end.
+
+     Notice (see examples below): 
+        if sent to Number, it will decide which type of number to return (depending on the exponent character);
+        if sent to a concrete number-class, an instance of that class will be returned (independent of the exponent character)
+    "
+
+    ^ self 
+        readFrom:aStringOrStream 
+        decimalPointCharacters:decimalPointCharacters 
+        thousandsSeparator:nil
+        allowCStyle:true 
+        onError:exceptionBlock
 
     "
-     Number readFrom:(ReadStream on:'54.32e-01')
+     Number readFrom:(ReadStream on:'54.32e-01') decimalPointCharacters:'.' onError:[self halt].
+
+     Number readFrom:(ReadStream on:'12345') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.0') decimalPointCharacters:'.' onError:[self halt].
+     
+     Number readFrom:(ReadStream on:'12345.0f') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.0e') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.0q') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.0d') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.0s') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.01s') decimalPointCharacters:'.' onError:[self halt].
+
+     Float readFrom:(ReadStream on:'12345') decimalPointCharacters:'.' onError:[self halt].
+     
      Number readFrom:(ReadStream on:'12345678901234567890')
      Number readFrom:(ReadStream on:'12345678901234567890.0')
      Number readFrom:(ReadStream on:'12345678901234567890.012345678901234567890')
-     Number readFrom:(ReadStream on:'16rAAAAFFFFAAAAFFFF')
+     Number readFrom:(ReadStream on:'16rAAAAFFFFAAAAFFFF')   
      Number readFrom:'16rAAAAFFFFAAAAFFFF'
+     Number readFrom:'16r100A'
+     Number readFrom:'16r100a'
      Number readFrom:'0.000001'
      '+00000123.45' asNumber
      Number readFrom:'(1/3)'
@@ -401,7 +534,342 @@
      Number readFrom:'99,00'
     "
 
-    "Modified: / 14.4.1998 / 19:22:50 / cg"
+    "Modified: / 17-07-2017 / 15:18:03 / cg"
+    "Modified: / 21-07-2019 / 13:05:19 / Claus Gittinger"
+    "Modified: / 17-12-2019 / 14:19:54 / Stefan Reise"
+!
+
+readFrom:aStringOrStream decimalPointCharacters:decimalPointCharacters thousandsSeparator:thousandsSeparator allowCStyle:allowCStyle onError:exceptionBlock
+    "return the next Number from the (character-)stream aStream;
+     skipping all whitespace first.
+     Return the value of exceptionBlock, if no number can be read.
+     This method is less strict than the Smalltalk number reader; 
+     it allows for prefixed + and also allows missing fractional part after eE.
+     It supports 0x, 0o and 0b prefixes (hex, octal and binary)
+     and the regular Smalltalk radix prefix xr.
+     If also allows for strings like '1.0×1015' to be read (as 1E+15).
+
+     It also allows garbage after the number - i.e. it reads what it can.
+     See #fromString: , which is more strict and does not allow garbage at the end.
+
+     Notice (see examples below): 
+        if sent to Number, it will decide which type of number to return (depending on the exponent character);
+        if sent to a concrete number-class, an instance of that class will be returned (independent of the exponent character)
+    "
+
+    ^ [
+        |value intValue mantissaAndScale scale str
+         nextChar radix sign signExp exp numerator denom expChar expChar2
+         fragment mantissa|
+
+        str := aStringOrStream readStream.
+
+        nextChar := str skipSeparators.
+        nextChar isNil ifTrue:[^ exceptionBlock value].
+
+        (nextChar == $-) ifTrue:[
+            sign := -1.
+            nextChar := str nextPeekOrNil
+        ] ifFalse:[
+            sign := 1.
+            (nextChar == $+) ifTrue:[
+                nextChar := str nextPeekOrNil
+            ]
+        ].
+        nextChar == $( ifTrue:[
+            "maybe a Fraction e.g. (1/3)"
+            str next.
+            numerator := Integer readFrom:str onError:[^ exceptionBlock value].
+            str skipSeparators.
+            nextChar := str peekOrNil.
+            nextChar == $/ ifTrue:[
+                str next.
+                denom := Integer readFrom:str onError:[^ exceptionBlock value].
+                str skipSeparators.
+                nextChar := str peekOrNil.
+            ].
+            nextChar == $) ifFalse:[^ exceptionBlock value].
+            str next.
+            value := Fraction numerator:numerator denominator:denom.
+            sign < 0 ifTrue:[ value := value negated ].
+            (self ~~ Number and:[self ~~ Fraction]) ifTrue:[
+                value := self coerce:value.
+            ].    
+            ^ value
+        ].
+        nextChar isNil ifTrue:[^ exceptionBlock value].
+        (nextChar isDigit or:[(decimalPointCharacters includes:nextChar)]) ifFalse:[
+            ^ exceptionBlock value.
+"/          value := super readFrom:str.
+"/          sign == -1 ifTrue:[value := value negated].
+"/          ^ value
+        ].
+        radix := 10.
+        (decimalPointCharacters includes:nextChar) ifTrue:[
+            self isAbstract ifTrue:[
+                value := 0.0.
+            ] ifFalse:[    
+                value := self zero. "/ 0.0.
+            ].
+            intValue := 0.
+        ] ifFalse:[
+            (allowCStyle and:[nextChar == $0]) ifTrue:[
+                nextChar := str nextPeekOrNil.
+                nextChar isNil ifTrue:[^ 0].
+                ((nextChar == $x) or:[nextChar == $X]) ifTrue:[ radix := 16 ] 
+                ifFalse:[ ((nextChar == $b) or:[nextChar == $B]) ifTrue:[ radix := 2 ] 
+                ifFalse:[ ((nextChar == $o) or:[nextChar == $O]) ifTrue:[ radix := 8 ]]].
+            ].
+            radix ~~ 10 ifTrue:[
+                nextChar := str nextPeekOrNil.  
+                (nextChar notNil and:[nextChar isDigitRadix:radix]) ifFalse:[
+                    ^ exceptionBlock value.
+                ].
+                value := Integer readFrom:str radix:radix.
+                nextChar := str peekOrNil.
+            ] ifFalse:[        
+                value := Integer readFrom:str radix:10.
+                nextChar := str peekOrNil.
+                [ thousandsSeparator notNil and:[nextChar == thousandsSeparator] ] whileTrue:[
+                    str next.
+                    fragment := str next:3.
+                    (fragment conform:#isDigit) ifFalse:[
+                        ^ exceptionBlock value.
+                    ].
+                    value := (value * 1000) + (Integer fastFromString:fragment at:1).
+                    nextChar := str peekOrNil.
+                ].    
+                ((nextChar == $r) or:[ nextChar == $R]) ifTrue:[
+                    str next.
+                    str peek == $- ifTrue:[
+                        sign := -1.
+                        str next
+                    ].
+                    radix := value.
+                    value := Integer readFrom:str radix:radix.
+                    nextChar := str peekOrNil.
+                ] ifFalse:[
+                    radix := 10
+                ].
+            ].        
+            intValue := value.
+        ].
+
+        (self == Integer or:[self inheritsFrom:Integer]) ifFalse:[
+            (decimalPointCharacters includes:nextChar) ifTrue:[
+                nextChar := str nextPeekOrNil.
+                (nextChar notNil and:[nextChar isDigitRadix:radix]) ifTrue:[
+                    mantissaAndScale := self readMantissaAndScaleFrom:str radix:radix.
+                    mantissa := mantissaAndScale first.
+                    value := (mantissa coerce:value) + mantissa.
+                    nextChar := str peekOrNil.
+                ]
+            ].
+
+            ('eEdDqQfF' includes:nextChar) ifTrue:[
+                expChar := nextChar.
+                nextChar := str nextPeekOrNil.
+                expChar == $Q ifTrue:[
+                    nextChar == $D ifTrue:[
+                        expChar2 := nextChar.
+                        nextChar := str nextPeekOrNil.
+                    ] ifFalse:[
+                        nextChar == $L ifTrue:[
+                            expChar2 := nextChar.
+                            nextChar := str nextPeekOrNil.
+                        ]
+                    ]
+                ].
+
+                signExp := 1.
+                (nextChar == $+) ifTrue:[
+                    nextChar := str nextPeekOrNil.
+                ] ifFalse:[
+                    (nextChar == $-) ifTrue:[
+                        nextChar := str nextPeekOrNil.
+                        signExp := -1
+                    ]
+                ].
+
+                "/ if I am abstract (i.e. I am Number or LPReal),
+                "/ let the exponent-character decide what kind of float we get:
+                "/      qQ   -> LongFloat
+                "/      eEdD -> Float      (which is ieee-double)
+                "/      fF   -> ShortFloat (which is ieee-float)
+                
+                self isAbstract ifTrue:[
+                    ('qQ' includes:expChar) ifTrue:[
+                        expChar2 == $D ifTrue:[
+                            value := value asQDouble
+                        ] ifFalse:[
+                            expChar2 == $L ifTrue:[
+                                value := value asLargeFloat
+                            ] ifFalse:[
+                                value := value asLongFloat.
+                            ]
+                        ]
+                    ] ifFalse:[
+                        ('fF' includes:expChar) ifTrue:[
+                            value := value asShortFloat.
+                        ] ifFalse:[    
+                            "/ maybe in the far future we might create shortfloats when seeing eE,
+                            "/ and only produce doubles on dD.
+                            "/ (for now, always create Doubles for Dolphin, Squeak etc. compatibility)
+
+                            false "('eE' includes:expChar)" ifTrue:[
+                                value := value asShortFloat
+                            ] ifFalse:[
+                                value := value asFloat.
+                            ].    
+                        ].    
+                    ].
+                ] ifFalse:[
+                    value := self coerce:value.
+                ].
+                
+                (nextChar notNil and:[(nextChar isDigitRadix:radix)]) ifTrue:[
+                    exp := (Integer readFrom:str radix:radix) * signExp.
+                    value := value * ((value class unity * 10.0) raisedToInteger:exp)
+                ]
+            ] ifFalse:[
+                ('sS' includes:nextChar) ifTrue:[
+                    nextChar := str nextPeekOrNil.
+                    (nextChar notNil and:[ nextChar isDigit]) ifTrue:[
+                        scale := (Integer readFrom:str).
+                    ].
+
+                    mantissaAndScale isNil ifTrue:[
+                        value := intValue asFixedPoint:(scale ? 0).
+                    ] ifFalse:[
+                        denom := 10 raisedTo:mantissaAndScale last.
+                        value := FixedPoint
+                                    numerator:(intValue * denom) + (mantissaAndScale second)
+                                    denominator:denom
+                                    scale:(scale ? mantissaAndScale third).
+                    ].
+                ] ifFalse:[
+                    (nextChar == $×) ifTrue:[
+                        (((nextChar := str nextPeek) == $1)
+                          and:[ ((nextChar := str nextPeek) == $0) ]
+                        ) ifTrue:[
+                            str next.
+                            exp := (Integer readFrom:str).
+                            value := value * ((value class unity * 10.0) raisedToInteger:exp).
+                        ] ifFalse:[
+                            ^ exceptionBlock value.
+                        ].
+                    ] ifFalse:[        
+                        (self inheritsFrom:LimitedPrecisionReal) ifTrue:[
+                            "when requesting a specific Float instance, coerce it.
+                             otherwise return a value without loosing precision"
+                            (self isAbstract not and:[value class == self]) ifFalse:[
+                                value := self coerce:value.
+                            ].
+                        ].
+                    ].
+                ].
+            ].
+        ].
+        sign == -1 ifTrue:[
+            value := value negated
+        ].
+        value.
+    ] on:Error do:exceptionBlock
+
+    "
+     Number readFrom:(ReadStream on:'54.32e-01') decimalPointCharacters:'.' onError:[self halt].
+
+     Number readFrom:(ReadStream on:'12345') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.0') decimalPointCharacters:'.' onError:[self halt].
+     
+     Number readFrom:(ReadStream on:'12345.0f') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.0e') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.0q') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.0d') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.0s') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12345.01s') decimalPointCharacters:'.' onError:[self halt].
+
+     Float readFrom:(ReadStream on:'12345') decimalPointCharacters:'.' onError:[self halt].
+     
+     Number readFrom:(ReadStream on:'12345678901234567890')
+     Number readFrom:(ReadStream on:'12345678901234567890.0')
+     Number readFrom:(ReadStream on:'12345678901234567890.012345678901234567890')
+     Number readFrom:(ReadStream on:'16rAAAAFFFFAAAAFFFF')
+     Number readFrom:'16rAAAAFFFFAAAAFFFF'
+     Number readFrom:'16r100A'
+     Number readFrom:'16r100a'  
+     Number readFrom:'16r-100A'      
+     Number readFrom:'-16r100A'      
+     Number readFrom:'0x100A'      
+     Number readFrom:'-0x100A'      
+     Number readFrom:'0x-100A'      
+     Number readFrom:'0.000001'
+     '+00000123.45' asNumber
+     Number readFrom:'(1/3)'
+     Number readFrom:'(-1/3)'
+     Number readFrom:'(1/-3)'
+     Number readFrom:'-(1/3)'
+     Number readFrom:'-(-1/3)'
+     Number readFrom:'(-1/3'
+     Number readFrom:'99s'
+     Number readFrom:'99.00s'
+     Number readFrom:'99.0000000s'
+     Number readFrom:'.0000000s'
+     Number readFrom:'.0000000q'
+     Number readFrom:'.0000000f'
+     Number readFrom:'.0000000e'
+     Number readFrom:'.0000000s1'
+     Number readFrom:'.0000000q1'
+     Number readFrom:'.0000000f1'
+     Number readFrom:'.0000000e1'
+     LongFloat readFrom:'.00000001'
+     Number readFrom:'.00000000000001'
+     Number readFrom:'.001'
+     ShortFloat readFrom:'.001'
+     Number readFrom:'123garbage'      -> returns 123
+     Number fromString:'123garbage'    -> raises an error
+
+     DecimalPointCharactersForReading := #( $. $, ).
+     Number readFrom:'99,00'
+
+     DecimalPointCharactersForReading := #( $. ).
+     Number readFrom:'99,00'
+    "
+
+    "Created: / 21-07-2019 / 13:05:04 / Claus Gittinger"
+    "Modified: / 21-07-2019 / 19:40:34 / Claus Gittinger"
+    "Modified (comment): / 17-12-2019 / 14:28:03 / Stefan Reise"
+!
+
+readFrom:aStringOrStream decimalPointCharacters:decimalPointCharacters thousandsSeparator:thousandsSeparator onError:exceptionBlock
+    "return the next Number from the (character-)stream aStream;
+     skipping all whitespace first.
+     Return the value of exceptionBlock, if no number can be read.
+     This method is less strict than the Smalltalk number reader; 
+     it allows for prefixed + and also allows missing fractional part after eE.
+     It supports the regular Smalltalk radix prefix xr.
+     It also allows garbage after the number - i.e. it reads what it can.
+     See #fromString: , which is more strict and does not allow garbage at the end.
+
+     Notice (see examples below): 
+        if sent to Number, it will decide which type of number to return (depending on the exponent character);
+        if sent to a concrete number-class, an instance of that class will be returned (independent of the exponent character)
+    "
+
+    ^ self 
+        readFrom:aStringOrStream 
+        decimalPointCharacters:decimalPointCharacters 
+        thousandsSeparator:thousandsSeparator
+        allowCStyle:false 
+        onError:exceptionBlock
+
+    "
+     Number readFrom:(ReadStream on:'12345') decimalPointCharacters:'.' onError:[self halt].
+     Number readFrom:(ReadStream on:'12,345.0') decimalPointCharacters:'.' thousandsSeparator:$, onError:[self halt].
+     Number readFrom:(ReadStream on:'12,1345.0') decimalPointCharacters:'.' thousandsSeparator:$, onError:[self halt].
+    "
+
+    "Created: / 21-07-2019 / 17:59:57 / Claus Gittinger"
 !
 
 readFrom:aStringOrStream onError:exceptionBlock
@@ -414,9 +882,9 @@
      See #fromString: , which is more strict and does not allow garbage at the end."
 
     ^ self
-	readFrom:aStringOrStream
-	decimalPointCharacters:(self decimalPointCharactersForReading)
-	onError:exceptionBlock
+        readFrom:aStringOrStream
+        decimalPointCharacters:(self decimalPointCharactersForReading)
+        onError:exceptionBlock
 
     "
      Number readFrom:(ReadStream on:'54.32e-01')
@@ -427,6 +895,7 @@
      Number readFrom:'16rAAAAFFFFAAAAFFFF'
      Number readFrom:'0.000001'
      '+00000123.45' asNumber
+     Number readFrom:'0'
      Number readFrom:'99s'
      Number readFrom:'99.00s'
      Number readFrom:'99.0000000s'
@@ -445,13 +914,16 @@
      DecimalPointCharactersForReading := #( $. ).
      Number readFrom:'99,00'
     "
+
+    "Modified (comment): / 17-12-2019 / 14:42:57 / Stefan Reise"
 !
 
 readSmalltalkSyntaxFrom:aStream
-    "ST-80 compatibility (thanks to a note from alpha testers)
-     read and return the next Number in smalltalk syntax from the
+    "ST-80 compatibility (thanks to a note from alpha testers).
+     Read and return the next Number in Smalltalk syntax from the
      (character-) aStream.
-     Returns nil if aStream contains no valid number."
+     Returns nil if aStream contains no valid number.
+     Notice that ST/X supports C-style integers, which VW does not"
 
     ^ self readSmalltalkSyntaxFrom:aStream onError:nil.
 
@@ -465,6 +937,8 @@
      Number readSmalltalkSyntaxFrom:'(1/10)'
 
      Number readSmalltalkSyntaxFrom:'(1/0)'
+     Number readSmalltalkSyntaxFrom:'0xA0'  
+     Number readSmalltalkSyntaxFrom:'0b1010'  
 
      Number readFrom:'(1/3)'
      Number readFrom:'(-1/3)'
@@ -486,7 +960,8 @@
      s next
     "
 
-    "Modified: / 19.11.1999 / 18:26:47 / cg"
+    "Modified: / 19-11-1999 / 18:26:47 / cg"
+    "Modified (comment): / 30-05-2020 / 11:22:26 / cg"
 !
 
 readSmalltalkSyntaxFrom:aStream onError:errorValue
@@ -498,29 +973,125 @@
     |n|
 
     [
-	n := Scanner scanNumberFrom:aStream.
+        n := Scanner scanNumberFrom:aStream.
     ] on:Error do:[:ex|
-	n := nil
+        n := nil
     ].
     n isNil ifTrue:[^ errorValue value].
     ^ n
 
     "
      Number readSmalltalkSyntaxFrom:'foo' onError:123
+     Number readSmalltalkSyntaxFrom:'16r123' onError:-1
+     Number readSmalltalkSyntaxFrom:'0x123' onError:-1   
+     Number readSmalltalkSyntaxFrom:'16r1.1' onError:-1  
+     Number readSmalltalkSyntaxFrom:'10r1.1' onError:-1    
+     Number readSmalltalkSyntaxFrom:'16r10.1' onError:-1  
+     Number readSmalltalkSyntaxFrom:'10r10.1' onError:-1    
+     Number readSmalltalkSyntaxFrom:'16r10.1e10' onError:-1  
+     Number readSmalltalkSyntaxFrom:'10r10.1e10' onError:-1    
     "
 ! !
 
 !Number class methodsFor:'Compatibility-VW'!
 
 readIntegerFrom:aStream radix:radix
-    "for VisualWorks compatibiity"
+    "for VisualWorks compatibility"
 
     ^ Integer readFrom:aStream radix:radix
+
+    "Modified (comment): / 08-06-2017 / 13:58:36 / mawalch"
 ! !
 
-
 !Number class methodsFor:'constants'!
 
+e
+    "return the closest approximation of the irrational number e"
+
+    ^ self subclassResponsibility
+
+    "Modified: / 16-06-2017 / 11:04:49 / cg"
+!
+
+eDigits
+    "return th printString of the irrational number e,
+     with enough digits so that instances with different precision can read from it"
+
+    "/ number asked from wolfram 
+    ^ '2.71828182845904523536028747135266249775724709369995957496696762772407663035354759457138217852516642742746'
+
+    "Created: / 06-06-2019 / 16:58:50 / Claus Gittinger"
+!
+
+i
+    "return the imaginary unit i"
+
+    
+    ^ Complex real:0 imaginary:1
+
+    "
+     1 + Number i          -> (1+1i)
+     Number i + 10         -> (10+1i)
+     Number i * Number i   -> -1
+    "
+
+    "Created: / 01-07-2017 / 19:44:53 / cg"
+    "Modified (comment): / 22-09-2017 / 09:53:14 / cg"
+!
+
+ln10
+    "return ln(10) in my representation (and accuracy)."
+
+    ^ self subclassResponsibility
+
+    "Created: / 16-06-2017 / 11:00:38 / cg"
+!
+
+ln2
+    "return ln(2) in my representation (and accuracy)."
+
+    ^ self subclassResponsibility
+
+
+!
+
+phi
+    "return Phi in my representation (and accuracy)."
+
+    ^ self subclassResponsibility
+
+
+!
+
+phiDigits
+    "return th printString of the irrational number pi,
+     with enough digits so that instances with different precision can read from it"
+
+    ^ '1.618033988749894848204586834365638117720309179805762862135'
+!
+
+pi
+    "return Pi in my representation (and accuracy)."
+
+    ^ self subclassResponsibility
+
+    "Modified (format): / 16-06-2017 / 11:00:42 / cg"
+!
+
+piDigits
+    "return th printString of the irrational number pi,
+     with enough digits so that instances with different precision can read from it"
+
+    "/ number asked from wolfram 
+    "/ ^ '3.1415926535897932384626433832795028841971693993751058209749445923078164062862089986280348253421170679821480865132823066470938446095505822317253594081284811174502841027019385211055596446229489549303819644288109756659334461284756482337867831652712019091456485669234603486104543266482133936072602491412737245870066063155881748815209209628292540917153643678925903600113305305488204665213841469519415116094330572703657595919530921861173819326117931051185480744623799627495673518857527248912279381830119491298336733624406566430860213949463952247371907021798609437027705392171762931767523846748184676694051320005681271452635608277857713427577896091736371787214684409012249534301465495853710507922796892589235420199561121290219608640344181598136297747713099605187072113499999983729780499510597317328160963185950244594553469083026425223082533446850352619311881710100031378387528865875332083814206171776691473035982534904'
+    "/ rounded to 100 digits
+    ^ '3.141592653589793238462643383279502884197169399375105820974944592307816406286208998628034825342117068'
+
+    "Created: / 06-06-2019 / 17:08:17 / Claus Gittinger"
+! !
+
+!Number class methodsFor:'constants & defaults'!
+
 decimalPointCharacter
     "printed"
 
@@ -630,8 +1201,160 @@
      Number fromString:'1,5'.
      Number decimalPointCharactersForReading:#( $. ).
     "
+! !
+
+!Number class methodsFor:'error reporting'!
+
+raise:aSignalSymbolOrErrorClass receiver:someNumber selector:sel arg:arg errorString:text
+    "ST-80 compatible signal raising. Provided for public domain numeric classes"
+
+    <context: #return>
+
+    ^ self
+        raise:aSignalSymbolOrErrorClass
+        receiver:someNumber
+        selector:sel
+        arguments:(Array with:arg)
+        errorString:text
+
+    "
+     Number
+        raise:#domainErrorSignal
+        receiver:1.0
+        selector:#sin
+        arg:nil
+        errorString:'foo bar test'
+    "
+
+    "Modified: / 16-11-2001 / 14:12:50 / cg"
+    "Modified (comment): / 30-05-2020 / 10:08:50 / cg"
 !
 
+raise:aSignalSymbolOrErrorClass receiver:someNumber selector:sel errorString:text
+    "ST-80 compatible signal raising. Provided for public domain numeric classes.
+     aSignalSymbolOrErrorClass is either an Error-subclass, or
+     the selector which is sent to myself, to retrieve the Exception class / Signal."
+
+    <context: #return>
+
+    ^ self
+        raise:aSignalSymbolOrErrorClass
+        receiver:someNumber
+        selector:sel
+        arguments:#()
+        errorString:text
+
+    "
+     Number
+        raise:#domainErrorSignal
+        receiver:1.0
+        selector:#foo
+        errorString:'foo bar test'
+    "
+
+    "Modified: / 16-11-2001 / 14:13:16 / cg"
+    "Modified (comment): / 30-05-2020 / 10:08:59 / cg"
+! !
+
+!Number class methodsFor:'misc'!
+
+displayRadix:aNumber
+    "being tired of always sending #printStringRadix: in the inspectors,
+     this allows you to change the default print radix for the displayString
+     method."
+
+    DefaultDisplayRadix := aNumber
+
+    "
+     Integer displayRadix:16. 123456 inspect
+     Integer displayRadix:10. 123456 inspect
+    "
+! !
+
+!Number class methodsFor:'private'!
+
+readMantissaAndScaleFrom:aStream radix:radix
+    "helper for readFrom: -
+     return the mantissa (post-decimal-point digits) from the (character-)stream aStream;
+     in addition, the mantissa as integer and the scale (number of postDecimalPoint digits) is returned
+     (both to support reading fixedPoint numbers and to not loose precision).
+     The integer mantissa is needed as we do not yet know the target type (could be LongFloat or even QDouble).
+     No whitespace is skipped."
+
+    |nextChar intMantissa scale digit scaleFactor value|
+
+    scale := 0.
+    scaleFactor := 1.
+    intMantissa := 0.
+    nextChar := aStream peekOrNil.
+    [nextChar notNil and:[nextChar isDigitRadix:radix]] whileTrue:[
+        digit := nextChar digitValue.
+        scaleFactor := scaleFactor * radix.
+        intMantissa := (intMantissa * radix) + digit.
+        scale := scale + 1.
+
+        aStream next.
+        nextChar := aStream peekOrNil
+    ].
+
+    self isAbstract ifFalse:[
+        value := (self coerce:intMantissa) / (self coerce:scaleFactor).
+    ] ifTrue:[
+        "/ Float decimalPrecision
+        "/ LongFloat decimalPrecision
+        scale > 6 ifTrue:[
+            "/ scale > 19 ifTrue:[
+            "/     value := intMantissa asLargeFloat / scaleFactor asLargeFloat.
+            "/ ] ifFalse:[
+                value := intMantissa asLongFloat / scaleFactor asLongFloat.
+            "/ ]
+        ] ifFalse:[
+            value := intMantissa asFloat / scaleFactor asFloat.
+        ].
+    ].    
+    ^ (Array with:value with:intMantissa with:scale).
+
+    "
+     Number readMantissaAndScaleFrom:'234'    readStream radix:10.
+     Number readMantissaAndScaleFrom:'2'      readStream radix:10.
+     Number readMantissaAndScaleFrom:'234567' readStream radix:10.
+     Number readMantissaAndScaleFrom:'234000' readStream radix:10.
+     Number readMantissaAndScaleFrom:'234'    readStream radix:10.
+     Number readMantissaAndScaleFrom:'000234' readStream radix:10.
+     Number readMantissaAndScaleFrom:'01' readStream radix:10.
+     Number readMantissaAndScaleFrom:'001' readStream radix:10.
+     Number readMantissaAndScaleFrom:'0001' readStream radix:10.
+     Number readMantissaAndScaleFrom:'000000000000000000000000000024' readStream radix:10.
+     Number readMantissaAndScaleFrom:'0000000000000000000000000000000000000000000024' readStream radix:10.
+     Number readMantissaAndScaleFrom:'123456789012345678901234567890' readStream radix:10. 
+     Number readMantissaAndScaleFrom:'1234567890123456789012345678901234567890' readStream radix:10. 
+
+     Number readMantissaAndScaleFrom:'12345678901234567890' readStream radix:10.
+    "
+
+    "Modified: / 17-06-2017 / 03:03:03 / cg"
+    "Modified: / 22-07-2019 / 19:37:21 / Claus Gittinger"
+!
+
+readMantissaFrom:aStream radix:radix
+    "helper for readFrom: -
+     return the mantissa (post-decimal-point digits)
+     from the (character-)stream aStream;
+     No whitespace is skipped."
+
+    ^ (self readMantissaAndScaleFrom:aStream radix:radix) first
+
+    "
+     Number readMantissaFrom:'234'    readStream radix:10.
+     Number readMantissaFrom:'2'      readStream radix:10.
+     Number readMantissaFrom:'234567' readStream radix:10.
+    "
+
+    "Modified: / 14.4.1998 / 18:47:47 / cg"
+! !
+
+!Number class methodsFor:'queries'!
+
 epsilon
     "return the maximum relative spacing of instances of mySelf
      (i.e. the value-delta of the least significant bit)"
@@ -654,145 +1377,6 @@
     "
 !
 
-pi
-    "return Pi in my representation (and accuracy)."
-
-     ^ self subclassResponsibility
-! !
-
-!Number class methodsFor:'error reporting'!
-
-raise:aSignalSymbolOrErrorClass receiver:someNumber selector:sel arg:arg errorString:text
-    "ST-80 compatible signal raising. Provided for PD numeric classes"
-
-    <context: #return>
-
-    ^ self
-	raise:aSignalSymbolOrErrorClass
-	receiver:someNumber
-	selector:sel
-	arguments:(Array with:arg)
-	errorString:text
-
-    "
-     Number
-	raise:#domainErrorSignal
-	receiver:1.0
-	selector:#sin
-	arg:nil
-	errorString:'foo bar test'
-    "
-
-    "Modified: / 16.11.2001 / 14:12:50 / cg"
-!
-
-raise:aSignalSymbolOrErrorClass receiver:someNumber selector:sel errorString:text
-    "ST-80 compatible signal raising. Provided for PD numeric classes.
-     aSignalSymbolOrErrorClass is either an Error-subclass, or
-     the selector which is sent to myself, to retrieve the Exception class / Signal."
-
-    <context: #return>
-
-    ^ self
-	raise:aSignalSymbolOrErrorClass
-	receiver:someNumber
-	selector:sel
-	arguments:#()
-	errorString:text
-
-    "
-     Number
-	raise:#domainErrorSignal
-	receiver:1.0
-	selector:#foo
-	errorString:'foo bar test'
-    "
-
-    "Modified: / 16.11.2001 / 14:13:16 / cg"
-! !
-
-!Number class methodsFor:'misc'!
-
-displayRadix:aNumber
-    "being tired of always sending #printStringRadix: in the inspectors,
-     this allows you to change the default print radix for the displayString
-     method."
-
-    DefaultDisplayRadix := aNumber
-
-    "
-     Integer displayRadix:16. 123456 inspect
-     Integer displayRadix:10. 123456 inspect
-    "
-! !
-
-
-!Number class methodsFor:'private'!
-
-readMantissaAndScaleFrom:aStream radix:radix
-    "helper for readFrom: -
-     return the mantissa (post-decimal-point digits) from the (character-)stream aStream;
-     In addition, the scale (number of postDecimalPoint digits) is returned
-     (to support reading fixedPoint numbers).
-     No whitespace is skipped.
-     Errs if no number is available on aStream."
-
-    |nextChar value factor intMantissa scale digit|
-
-    value := 0.0.
-    factor := 1.0 / radix.
-    scale := 0.
-    intMantissa := 0.
-    nextChar := aStream peekOrNil.
-    [nextChar notNil and:[nextChar isDigitRadix:radix]] whileTrue:[
-	digit := nextChar digitValue.
-	value := value + (digit * factor).
-	intMantissa := (intMantissa * radix) + digit.
-	factor := factor / radix.
-	scale := scale + 1.
-	scale > 6 ifTrue:[
-	    factor := factor asLongFloat.
-	    value := value asLongFloat.
-	].
-	aStream next.
-	nextChar := aStream peekOrNil
-    ].
-
-    ^ (Array with:value with:intMantissa with:scale).
-
-    "
-     Number readMantissaAndScaleFrom:'234'    readStream radix:10.
-     Number readMantissaAndScaleFrom:'2'      readStream radix:10.
-     Number readMantissaAndScaleFrom:'234567' readStream radix:10.
-     Number readMantissaAndScaleFrom:'234000' readStream radix:10.
-     Number readMantissaAndScaleFrom:'234'    readStream radix:10.
-
-     Number readMantissaAndScaleFrom:'12345678901234567890' readStream radix:10.
-    "
-
-    "Modified: / 14.4.1998 / 18:47:47 / cg"
-!
-
-readMantissaFrom:aStream radix:radix
-    "helper for readFrom: -
-     return the mantissa (post-decimal-point digits)
-     from the (character-)stream aStream;
-     No whitespace is skipped.
-     Errs if no number available."
-
-    ^ (self readMantissaAndScaleFrom:aStream radix:radix) first
-
-    "
-     Number readMantissaFrom:'234'    readStream radix:10.
-     Number readMantissaFrom:'2'      readStream radix:10.
-     Number readMantissaFrom:'234567' readStream radix:10.
-    "
-
-    "Modified: / 14.4.1998 / 18:47:47 / cg"
-! !
-
-!Number class methodsFor:'queries'!
-
 isAbstract
     "Return if this class is an abstract class.
      True is returned for Number here; false for subclasses.
@@ -801,7 +1385,6 @@
     ^ self == Number
 ! !
 
-
 !Number methodsFor:'Compatibility-Squeak'!
 
 asSmallAngleDegrees
@@ -820,7 +1403,11 @@
 !
 
 closeFrom:aNumber
-    "are these two numbers close?"
+    "are these two numbers close?
+     Notice, that this is definitely not the best way to compensate
+     for rounding errors - see isAlmostEqualTo:aNumber nEpsilon:nE
+     (or at least, use closeFrom:withEpsilon:,
+      where the epsilon is given as arg)"
 
     ^ self closeFrom:aNumber withEpsilon:(self class epsilonForCloseTo)
 
@@ -843,7 +1430,12 @@
 !
 
 closeFrom:aNumber withEpsilon:eps
-    "are these two numbers close?"
+    "are these two numbers close?
+     That is, within the given epsilon.
+     Notice, that this is probably not the best way to compensate
+     for rounding errors - see isAlmostEqualTo:aNumber nEpsilon:nE
+     (although it is useful to determine if a measured value
+      is within its spec)"
 
     | fuzz |
 
@@ -851,28 +1443,40 @@
     self isInfinite == aNumber isInfinite ifFalse: [^ false].
 
     fuzz := (self abs max:aNumber abs) * eps.
+    fuzz isFinite ifFalse:[^ false].
+
     ^ (self - aNumber) abs <= fuzz
 
     "
      9.0 closeTo: 8.9999
+     9.0 closeTo: 8.9999 withEpsilon:0.1
+     9.0 closeTo: 8.9999 withEpsilon:0.0001
+     9.0 closeTo: 8.9999 withEpsilon:0.00001
+
      9.9 closeTo: 9
+     9.9 closeTo: 9 withEpsilon:1
+     
      (9/3) closeTo: 2.9999
      1 closeTo: 0.9999
+     1 closeTo: 0.9999 withEpsilon:0.0001
+     1 closeTo: 0.9999 withEpsilon:0.00001
+     
      1 closeTo: 1.0001
      1 closeTo: 1.001
      1 closeTo: 0.999
 
-     0.9999 closeTo: 1
-     1.0001 closeTo: 1
-     1.001 closeTo: 1
-     0.999 closeTo: 1
-     Float NaN closeTo:Float NaN
-     Float infinity closeTo:Float infinity
+     170 closeTo:(170 raisedTo:240)
     "
+
+    "Modified (comment): / 31-08-2018 / 12:24:39 / Claus Gittinger"
 !
 
 closeTo:num
-    "are these two numbers close to each other?"
+    "are these two numbers close to each other?
+     Notice, that this is definitely not the best way to compensate
+     for rounding errors - see isAlmostEqualTo:aNumber nEpsilon:nE
+     (or at least, use closeFrom:withEpsilon:,
+      where the epsilon is given as arg)"
 
     ^ self closeTo:num withEpsilon:(self class epsilonForCloseTo)
 
@@ -886,7 +1490,11 @@
 !
 
 closeTo:num withEpsilon:eps
-    "are these two numbers close to each other?"
+    "are these two numbers close to each other?
+     Notice, that this is probably not the best way to compensate
+     for rounding errors - see isAlmostEqualTo:aNumber nEpsilon:nE
+     (although it is useful to determine if a measured value
+      is within its spec)"
 
     num isNumber ifFalse:[^false].
     ^ num closeFrom:self withEpsilon:eps
@@ -906,26 +1514,13 @@
     "Modified: / 02-08-2010 / 13:27:22 / cg"
 !
 
-degreeCos
-    "Return the cosine of the receiver taken as an angle in degrees."
-
-    ^ self degreesToRadians cos
-!
-
-degreeSin
-    "Return the sine of the receiver taken as an angle in degrees."
-
-    ^ self degreesToRadians sin
-!
-
-degreeTan
-    "Return the cosine of the receiver taken as an angle in degrees."
-
-    ^ self degreesToRadians tan
-!
-
 isEqual: aNumber within: accuracy
-	^(self - aNumber) abs < accuracy
+     "Notice, that this is probably not the best way to compensate
+     for rounding errors - see isAlmostEqualTo:aNumber nEpsilon:nE
+     (although it is useful to determine if a measured value
+      is within its spec)"
+
+    ^ (self - aNumber) abs < accuracy
 !
 
 rounded:n
@@ -934,47 +1529,58 @@
     | mult |
 
     mult := 10 raisedTo: n.
-    ^ (((self * mult) rounded) asFloat / mult).
+    ^ (((self * mult) rounded) asLimitedPrecisionReal / mult).
 
     "
      7 rounded:2
      7.1 rounded:2
-     7.2345 rounded:2
-     7.2385 rounded:2
-     7.2341 rounded:3
+     7.2345 rounded:2  -> 7.23 
+     7.2385 rounded:2  -> 7.24 
+     7.2341 rounded:3  -> 7.234
      7.2345 rounded:3
      7.2348 rounded:3
+     (1/3) rounded:3   -> 0.333
+     (2/3) rounded:3   -> 0.667
     "
-!
-
-stringForReadout
-    ^ self rounded printString
 ! !
 
-
 !Number methodsFor:'coercing & converting'!
 
 i
     "return a complex number, with the receiver as imaginary part, 0 as real part"
 
-    ^ Complex
-	real:0
-	imaginary:self
+    ^ Complex real:0 imaginary:self
 
     "
-     3i
-     (1+1i)
+     3i     -> (0+3i)
+     (1+1i) -> (1+1i)
     "
+
+    "Modified (format): / 22-09-2017 / 09:53:27 / cg"
 ! !
 
 !Number methodsFor:'comparing'!
 
+epsilonForCloseTo
+    "return the epsilon used in the closeTo: comparison."
+
+    ^ self class epsilonForCloseTo
+
+    "
+     1.0 epsilon
+     10 asShortFloat epsilon
+    "
+
+    "Created: / 10-06-2019 / 21:20:18 / Claus Gittinger"
+!
+
 isAlmostEqualTo:aNumber nEpsilon:nE
     "return true, if the argument, aNumber represents almost the same numeric value
      as the receiver, false otherwise.
 
      nE is the number of minimal float distances, that the numbers may differ and
-     still be considered equal. See documentation in LimitedPrecisionReal for more detail.
+     still be considered equal. 
+     See documentation in LimitedPrecisionReal for more detail.
 
      For background information why floats need this
      read: http://randomascii.wordpress.com/2012/02/25/comparing-floating-point-numbers-2012-edition/
@@ -987,15 +1593,35 @@
     scaledEpsilon := nE * diff class epsilon.
 
     diff <= scaledEpsilon ifTrue:[
-	"compare for really close values near 0"
-	^ true.
-    ] ifFalse:[
-	"scaled comparison for larger values"
-	f1 := self abs.
-	f2 := aNumber abs.
-	largest := f1 > f2 ifTrue:[f1] ifFalse:[f2].
-	^ (diff <= (scaledEpsilon * largest)).
+        "compare for really close values near 0"
+        ^ true.
     ].
+
+    "scaled comparison for larger values"
+    f1 := self abs.
+    f2 := aNumber abs.
+    largest := f1 > f2 ifTrue:[f1] ifFalse:[f2].
+    ^ (diff <= (scaledEpsilon * largest)).
+
+    "Modified: / 15-06-2017 / 09:55:15 / cg"
+!
+
+isAlmostEqualTo:aNumber withError:errFraction
+    "return true, if the receiver,is inside the interval 
+     aNumber-err .. aNumber+err.
+     Err should be a fraction of 0..1."
+
+    ^ self between:(aNumber * (1-errFraction)) and:(aNumber * (1+errFraction))
+
+    "
+     within 10%?
+     10.5 isAlmostEqualTo:10 withError:0.1
+
+     within 1%
+     10.5 isAlmostEqualTo:10 withError:0.01
+    "
+
+    "Created: / 23-09-2017 / 16:33:26 / cg"
 ! !
 
 !Number methodsFor:'converting'!
@@ -1064,7 +1690,18 @@
 !
 
 asMetaNumber
+    self isNaN ifTrue:[
+        ^ NotANumber NaN
+    ].    
     ^ SomeNumber new realNumber:self
+
+    "
+     Float NaN asMetaNumber
+     Float infinity asMetaNumber
+     Float negativeInfinity asMetaNumber
+    "
+
+    "Modified (comment): / 21-06-2017 / 20:47:59 / cg"
 !
 
 asNumber
@@ -1109,8 +1746,8 @@
 !
 
 asTimeDuration
-    "return an TimeDuration object from the receiver, taking the receiver
-     as number of seconds"
+    "return an TimeDuration object from the receiver, 
+     taking the receiver as number of seconds"
 
     ^ TimeDuration seconds:self
 
@@ -1118,9 +1755,11 @@
      5 asTimeDuration
      50.25 asTimeDuration
      3600 asTimeDuration
+     '5m' asTimeDuration
     "
 
     "Created: / 08-01-2012 / 19:04:04 / cg"
+    "Modified (comment): / 21-01-2019 / 10:31:15 / Claus Gittinger"
 !
 
 degreesToRadians
@@ -1209,14 +1848,44 @@
     "
 !
 
+microseconds
+    "return a TimeDuration representing this number of microseconds."
+
+    ^ TimeDuration fromMicroseconds:self
+
+    "
+     40 microseconds
+    "
+
+    "Modified (comment): / 21-09-2017 / 17:37:18 / cg"
+!
+
+milliSeconds
+    "return a TimeDuration representing this number of milliseconds
+     Same as milliseconds, for dialect compatibility"
+
+    ^ TimeDuration fromMilliseconds:self
+
+    "
+     1000 milliSeconds
+    "
+
+    "Created: / 21-09-2017 / 17:26:32 / cg"
+    "Modified (comment): / 18-07-2019 / 21:33:09 / Claus Gittinger"
+!
+
 milliseconds
-    "return a TimeDuration representing this number of milliseconds"
+    "return a TimeDuration representing this number of milliseconds.
+     Same as milliSeconds, for dialect compatibility"
 
     ^ TimeDuration fromMilliseconds:self
 
     "
      1000 milliseconds
     "
+
+    "Modified (comment): / 21-09-2017 / 17:37:18 / cg"
+    "Modified (comment): / 18-07-2019 / 21:33:12 / Claus Gittinger"
 !
 
 minutes
@@ -1231,6 +1900,36 @@
     "
 !
 
+nanoseconds
+    "return a TimeDuration representing this number of nanoseconds."
+
+    ^ TimeDuration fromNanoseconds:self
+
+    "
+     40.5 nanoseconds asPicoseconds
+     (40.5 nanoseconds / 2) asPicoseconds
+
+     40 nanoseconds
+     40 nanoseconds asPicoseconds
+     44 milliseconds asMicroseconds
+     44 milliseconds 
+    "
+
+    "Modified (comment): / 21-09-2017 / 17:37:18 / cg"
+!
+
+picoseconds
+    "return a TimeDuration representing this number of picoseconds."
+
+    ^ TimeDuration fromPicoseconds:self
+
+    "
+     40 picoseconds
+    "
+
+    "Modified (comment): / 21-09-2017 / 17:37:18 / cg"
+!
+
 seconds
     "return a TimeDuration representing this number of seconds"
 
@@ -1259,6 +1958,17 @@
     "Created: / 05-09-2011 / 11:17:59 / cg"
 ! !
 
+!Number methodsFor:'copying'!
+
+deepCopyUsing:aDictionary postCopySelector:postCopySelector
+    "return a deep copy of myself
+     - reimplemented here since numbers are immutable"
+
+    ^ self
+
+    "Modified (comment): / 23-05-2020 / 20:03:00 / cg"
+! !
+
 !Number methodsFor:'double dispatching'!
 
 differenceFromTimestamp:aTimestamp
@@ -1277,6 +1987,16 @@
     "
 ! !
 
+!Number methodsFor:'inspecting'!
+
+inspectorValueStringInListFor:anInspector
+    "returns a string to be shown in the inspector's list"
+
+    ^ self printString contractTo:30
+
+    "Created: / 29-05-2019 / 15:01:19 / Claus Gittinger"
+! !
+
 !Number methodsFor:'intervals'!
 
 downTo:stop
@@ -1337,10 +2057,60 @@
 	aBlock value.
 	count := count - 1
     ]
+!
+
+timesRepeatWithExit:aOneArgBlock
+    "evaluate the argument, aBlock self times;
+     pass an exit block to the one-arg-block"
+
+    |count exit|
+
+    exit := [:values | ^ values firstIfEmpty:nil] asVarArgBlock.
+    count := self.
+    [count > 0] whileTrue:[
+        aOneArgBlock value:exit.
+        count := count - 1
+    ]
+
+    "
+    10 timesRepeatWithExit:[:exit |
+        Transcript showCR:'iteration'.
+        (Random nextBetween:1 and:10) > 7 ifTrue:[exit value].
+    ].
+    "
+
+    "Created: / 28-06-2019 / 12:01:24 / Claus Gittinger"
 ! !
 
 !Number methodsFor:'mathematical functions'!
 
+agm:y
+    "return the arithmetic-geometric mean agm(x, y) of the receiver (x) and the argument, y.
+     See https://en.wikipedia.org/wiki/Arithmetic-geometric_mean
+     and http://www.wolframalpha.com/input/?i=agm(24,+6)"
+
+    |ai an gi gn epsilon delta|
+
+    ai := (self + y) / 2.
+    gi := (self * y) sqrt.
+    epsilon := self epsilon.
+
+    [
+        an := (ai + gi) / 2.
+        gn := (ai * gi) sqrt.
+        delta := (an - ai) abs.
+        ai := an.
+        gi := gn.
+    ] doUntil:[ delta < epsilon ].
+    ^ ai
+
+    "
+     24 agm:6
+    "
+
+    "Created: / 03-07-2017 / 12:05:00 / cg"
+!
+
 cbrt
     "return the cubic root of the receiver"
 
@@ -1348,10 +2118,16 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat cbrt.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f cbrt.
+        ].
     ].
     "/ very slow fallback
     ^ self cbrt_withAccuracy:self epsilon
+
+    "Modified: / 05-07-2017 / 17:23:27 / cg"
 !
 
 conjugated
@@ -1369,10 +2145,27 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat exp.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f exp.
+        ].
     ].
     "/ very slow fallback
     ^ self exp_withAccuracy:self epsilon
+
+    "Modified: / 05-07-2017 / 17:23:36 / cg"
+!
+
+fibPhi
+    ^ (1 / 5 sqrt) * ((self class phi raisedTo:self) - ((-1 / self class phi) raisedTo:self))
+
+    "
+     3 fib      
+     3.0 fibPhi   
+     100 fib     
+     100.0 fibPhi  
+    "
 !
 
 floorLog:radix
@@ -1382,11 +2175,32 @@
 !
 
 imaginary
-    "Return the imaginary part of this Number."
+    "Return the imaginary part of a complex number.
+     For non-complex numbers, zero is returned."
 
     ^ 0
 
-    "Modified: / 9.7.1998 / 10:17:24 / cg"
+    "Modified: / 09-07-1998 / 10:17:24 / cg"
+    "Modified (comment): / 01-06-2018 / 13:09:09 / Claus Gittinger"
+!
+
+ldexp:exp
+    "multiply the receiver by an integral power of 2.
+     I.e. return self * (2 ^ exp).
+     This is also the operation to reconstruct the original float from its
+     mantissa and exponent: (f mantissa ldexp:f exponent) = f"
+
+    ^ self * (2 raisedTo:exp)
+
+    "
+     1.0 ldexp:16  -> 65536.0
+     1.0 ldexp:100 -> 1.26765060022823E+30
+     1 * (2 raisedToInteger:100) -> 1267650600228229401496703205376
+     1 ldexp:200   -> 1606938044258990275541962092341162602522202993782792835301376
+     1.0 ldexp:200 -> 1.60693804425899E+60
+    "
+
+    "Created: / 19-06-2017 / 01:43:35 / cg"
 !
 
 ln
@@ -1397,14 +2211,20 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asLongFloat ln.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f ln.
+        ].
     ].
     "/ very slow fallback
     ^ self ln_withAccuracy:self epsilon
 
     "
-	(10 raisedTo:1000) ln
+     (10 raisedTo:1000) ln
     "
+
+    "Modified: / 05-07-2017 / 17:23:50 / cg"
 !
 
 log
@@ -1415,16 +2235,53 @@
 !
 
 log10
-    "return log base 10 of the receiver"
+    "return log base-10 of the receiver.
+     Raises an exception, if the receiver is less or equal to zero.
+     Here, fallback to the general logarithm code."
 
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asLongFloat log10.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f log10.
+        ].
     ].
-    ^ self log:10
+    ^ self ln / self class ln10
 
     "
-	(10 raisedTo:1000) log10
+     (10 raisedTo:1000) log10
+     (10 raisedTo:2000) log10
+     (10 raisedTo:4000) log10
+     (10 raisedTo:8000) log10
+    "
+
+    "Modified: / 05-07-2017 / 17:23:06 / cg"
+!
+
+log2
+    "return log base-2 of the receiver.
+     Raises an exception, if the receiver is less or equal to zero.
+     Here, fallback to the general logarithm code."
+
+    (self isLimitedPrecisionReal not
+    or:[self generality < 1.0 generality]) ifTrue:[
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f log2.
+        ].
+    ].
+    ^ self ln / self class ln2
+
+    "
+     2.0 log2  
+     4.0 log2  
+     (2.0 raisedTo:100.0) log2  
+     (10 raisedTo:1000) log2
+     (10 raisedTo:2000) log2
+     (10 raisedTo:4000) log2
+     (10 raisedTo:8000) log2
     "
 !
 
@@ -1442,6 +2299,33 @@
     "
 !
 
+nthRoot:n
+    "return the nth root of the receiver"
+
+    n == 2 ifTrue:[^ self sqrt ].
+    n == 3 ifTrue:[^ self cbrt ].
+    "/ slow fallback
+    ^ self nthRoot:n withAccuracy:self epsilon
+
+    "
+     10 nthRoot:2 -> 3.16227766016838
+     10 nthRoot:3 -> 2.154434690031883722
+
+     100.0 nthRoot:4 
+     100.0 nthRoot:5
+     (100.0 nthRoot:6) raisedTo:6
+
+     16.0 nthRoot:2
+     -16.0 nthRoot:3
+     -16.0 nthRoot:5
+     
+     -16.0 nthRoot:4
+    "
+
+    "Created: / 25-07-2017 / 16:15:11 / cg"
+    "Modified (comment): / 22-09-2017 / 10:15:33 / cg"
+!
+
 raisedTo:aNumber
     "return the receiver raised to aNumber"
 
@@ -1468,11 +2352,13 @@
 !
 
 real
-    "Return the real part of this Number."
+    "Return the real part of a complex number.
+     For non-complex numbers, the receiver is returned."
 
     ^ self
 
-    "Modified: / 9.7.1998 / 10:17:17 / cg"
+    "Modified: / 09-07-1998 / 10:17:17 / cg"
+    "Modified (comment): / 01-06-2018 / 13:09:33 / Claus Gittinger"
 !
 
 sqrt
@@ -1482,28 +2368,32 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat sqrt.
+        |f|
+
+        "/ do not make this a LongFloat;
+        "/ it will return a LongFloat then, and Image rotated will fail then...
+        (f := self asFloat) isFinite ifTrue:[
+            ^ f sqrt.
+        ].
     ].
     "/ very slow fallback
     ^ self sqrt_withAccuracy:self epsilon
+
+    "Modified (format): / 11-07-2017 / 13:32:02 / cg"
+    "Modified (format): / 26-07-2017 / 12:30:16 / mawalch"
 !
 
 sqrtWithErrorLessThan:epsilon
     "compute the square root, using the Newton method.
      The approximated return value has an error less than the given epsilon."
 
-    |y yN|
-
-    yN := self / 2.
-    [
-       y := yN.
-       yN := ( y + (self / y) ) / 2.
-    ] doUntil:[ (yN - y) abs < epsilon ].
-    ^ yN.
+    ^ self sqrt_withAccuracy:epsilon
 
     "
      (2 asFixedPoint:4) sqrtWithErrorLessThan:0.001
     "
+
+    "Modified: / 25-07-2017 / 15:58:46 / cg"
 !
 
 timesTwoPower:anInteger
@@ -1511,18 +2401,22 @@
      For protocol completeness wrt. Squeak and ST80."
 
     anInteger >= 0 ifTrue:[
-	^ self * (1 bitShift:anInteger)
+        ^ self * (1 bitShift:anInteger)
     ].
     ^ self / (1 bitShift:anInteger negated)
 
     "
-     123 timesTwoPower:0   -> 123
-     123 timesTwoPower:1   -> 246
-     123 timesTwoPower:2   -> 492
-     123 timesTwoPower:3   -> 984
+     123 timesTwoPower:0  = 123*1 -> 123
+     123 timesTwoPower:1  = 123*2 -> 246
+     123 timesTwoPower:2  = 123*4 -> 492
+     123 timesTwoPower:3  = 123*8 -> 984
 
      (2 timesTwoPower: -150) timesTwoPower: 150  -> 2
+     (2 timesTwoPower: 150) timesTwoPower: -150  -> 2
+     (2 timesTwoPower: 150) timesTwoPower: -149  -> 4  
     "
+
+    "Modified (comment): / 26-05-2019 / 03:26:09 / Claus Gittinger"
 ! !
 
 !Number methodsFor:'measurement values'!
@@ -1549,15 +2443,15 @@
      DefaultDisplayRadix (see Integer>>displayRadix:)"
 
     "/ what a kludge - Dolphin and Squeak mean: printOn: a stream;
-    "/ ST/X (and some old ST80's) mean: draw-yourself on a GC.
+    "/ old ST80 means: draw-yourself on a GC.
     (aGCOrStream isStream) ifFalse:[
-	^ super displayOn:aGCOrStream
+        ^ super displayOn:aGCOrStream
     ].
 
     (DefaultDisplayRadix isNil or:[DefaultDisplayRadix == 10]) ifTrue:[
-	self printOn:aGCOrStream
+        self printOn:aGCOrStream
     ] ifFalse:[
-	self printOn:aGCOrStream base:DefaultDisplayRadix showRadix:true.
+        self printOn:aGCOrStream base:DefaultDisplayRadix showRadix:true.
     ].
 
     "
@@ -1565,6 +2459,8 @@
      Integer displayRadix:2.  12345
      Integer displayRadix:10. 12345
     "
+
+    "Modified (comment): / 22-02-2017 / 16:52:16 / cg"
 !
 
 printOn:aStream
@@ -1679,7 +2575,19 @@
 !
 
 printStringFormat:formatString
-    ^ self printfPrintString:formatString
+    "Return a printed representation of the receiver as specified by formatString,
+     which is defined by PrintfScanf."
+
+    ^ PrintfScanf printf:formatString argument:self.
+    "/ ^ self printfPrintString:formatString
+
+    "
+     1.2345 printStringFormat:'%4.2f' -> '1.23'
+     123 printStringFormat:'%4d' -> ' 123'
+     123 printStringFormat:'%5.2f' -> '123.0'
+    "
+
+    "Modified (comment): / 03-06-2018 / 09:15:01 / Claus Gittinger"
 !
 
 printStringRadix:base
@@ -1697,10 +2605,10 @@
 !
 
 printStringRadix:base showRadix:showRadixBoolean
-    "return a string representation of the receiver in the specified
-     base; does NOT prepend XXr to the string.
+    "return a string representation of the receiver in the specified base; 
+     optionally prepend XXr to the string.
      See also: radixPrintStringRadix:
-	       printOn:base:showRadix:"
+               printOn:base:showRadix:"
 
     |s|
 
@@ -1713,8 +2621,8 @@
      10000000000000000000000000000000000000000000 printStringRadix:16 showRadix:true
     "
 
-
     "Created: / 23-09-2011 / 13:59:19 / cg"
+    "Modified (comment): / 22-06-2018 / 09:56:17 / Claus Gittinger"
 !
 
 printStringWithThousandsSeparator
@@ -1782,6 +2690,22 @@
     "
 !
 
+printfPrintString:formatString
+    "Return a printed representation of the receiver as specified by formatString,
+     which is defined by printf."
+
+    ^ PrintfScanf printf:formatString argument:self
+
+    "
+     2.0 asQDouble printfPrintString:'%10f'
+     2.0 asQDouble printfPrintString:'%10.8f'
+     2.0 printfPrintString:'%10.8f'
+     12345 printfPrintString:'0x%06x' 
+    "
+
+    "Created: / 22-06-2017 / 13:55:22 / cg"
+!
+
 radixPrintStringRadix:radix
     "return a string representation of the receiver in the specified
      base; prepend XXr to the string"
@@ -1828,15 +2752,15 @@
     |x2 num numf den denf approx delta|
 
     ((self < -1) or:[self > 1]) ifTrue:[
-	^ self class
-	    raise:#domainErrorSignal
-	    receiver:self
-	    selector:#arcSin
-	    arguments:#()
-	    errorString:'bad receiver in arcSin'
+        ^ self class
+            raise:#domainErrorSignal
+            receiver:self
+            selector:#arcSin
+            arguments:#()
+            errorString:'bad receiver in arcSin'
     ].
 
-    x2 := self * self.
+    x2 := self squared.
     num := x2 * self.
     approx := self + (num / 6).
 
@@ -1845,11 +2769,11 @@
     den := 2.
 
     [
-	num := (num * x2) * numf.   numf := numf + 2.
-	den := den * denf.          denf := denf + 2.
-
-	delta := num / (den * numf).
-	approx := approx + delta.
+        num := (num * x2) * numf.   numf := numf + 2.
+        den := den * denf.          denf := denf + 2.
+
+        delta := num / (den * numf).
+        approx := approx + delta.
     ] doUntil:[delta abs <= epsilon].
     ^ approx
 
@@ -1891,18 +2815,18 @@
 
     |x2 num den approx delta|
 
-    x2 := self * self.
+    x2 := self squared.
 
     num := (x2 * self) negated.
     den := 3.
     approx := self + (num / den).
 
     [
-	den := den + 2.
-	num := (num * x2) negated.
-
-	delta := num / den.
-	approx := approx + delta.
+        den := den + 2.
+        num := (num * x2) negated.
+
+        delta := num / den.
+        approx := approx + delta.
     ] doUntil:[delta abs <= epsilon].
     ^ approx
 
@@ -1935,58 +2859,60 @@
 cbrt_withAccuracy:epsilon
     "compute cubic root of the receiver using a newton approx."
 
-    "
-      Use Newton's method:
-
-		 2*x_n + (a / x_n^2)
-	x_n+1 =  ---------------
-		      3
-
-	cbrt(a) = x_n
+    "Use Newton's method (not taylor):
+
+                 2*x_n + (a / x_n^2)
+        x_n+1 =  ---------------
+                      3
+
+        cbrt(a) = x_n
     "
 
     |approx|
 
     self = 0 ifTrue:[
-	^ self
+        ^ self
     ].
 
     approx := 1.
     [
-	|lastApprox|
-
-	lastApprox := approx.
-	approx := ((approx * 2) + (self / approx / approx)) / 3.
-	(approx - lastApprox) abs > epsilon
+        |lastApprox|
+
+        lastApprox := approx.
+        approx := ((approx * 2) + (self / approx / approx)) / 3.
+        (approx - lastApprox) abs > epsilon
     ] whileTrue.
     ^ approx
 
     "
-     8q cbrt                                 2.0
-     8q cbrt_withAccuracy:0.01               2.000004911675504018
-     8q cbrt_withAccuracy:0.0001             2.000000000012062239
-     8q cbrt_withAccuracy:0.0000001          2.0
-     8q cbrt_withAccuracy:0.0000000001       2.0
-     8q cbrt_withAccuracy:0.000000000001     2.0
-     8q cbrt_withAccuracy:LongFloat epsilon  2.0
-
-     27q cbrt_withAccuracy:0.01              3.000000541064176501
-     27q cbrt_withAccuracy:LongFloat epsilon  3.0
-     -27q cbrt_withAccuracy:LongFloat epsilon -3.0
+     8q cbrt                                         2.0
+     8q cbrt_withAccuracy:0.01                       2.000004911675504018
+     8q cbrt_withAccuracy:0.0001                     2.000000000012062239
+     8q cbrt_withAccuracy:0.0000001                  2.0
+     8q cbrt_withAccuracy:0.0000000001               2.0
+     8q cbrt_withAccuracy:0.000000000001             2.0
+     8q cbrt_withAccuracy:LongFloat epsilon          2.0
+     8q asQDouble cbrt_withAccuracy:QDouble epsilon  2.0
+
+     27q cbrt_withAccuracy:0.01                      3.000000541064176501
+     27q cbrt_withAccuracy:LongFloat epsilon         3.0
+     -27q cbrt_withAccuracy:LongFloat epsilon        -3.0
 
      MessageTally spyOn:[ |arg|
-	arg := 2 asLongFloat.
-	1000000 timesRepeat:[
-	     arg cbrt_withAccuracy:0.000000000001
-	]
+        arg := 2 asLongFloat.
+        1000000 timesRepeat:[
+             arg cbrt_withAccuracy:0.000000000001
+        ]
      ]
      Time millisecondsToRun:[ |arg|
-	arg := 2 asLongFloat.
-	1000000 timesRepeat:[
-	     arg cbrt_withAccuracy:0.000000000001
-	]
+        arg := 2 asLongFloat.
+        1000000 timesRepeat:[
+             arg cbrt_withAccuracy:0.000000000001
+        ]
      ]
     "
+
+    "Modified (comment): / 25-07-2017 / 16:09:22 / cg"
 !
 
 cos_withAccuracy:epsilon
@@ -1999,7 +2925,7 @@
 
     |x2 facN num den approx lastApprox|
 
-    x2 := self * self.
+    x2 := self squared.
 
     num := x2 negated.
     den := 2.
@@ -2008,22 +2934,28 @@
     lastApprox := 1.
 
     [ (lastApprox - approx) abs > epsilon ] whileTrue:[
-	facN := facN + 2.
-	den := den * (facN - 1) * facN.
-	num := (num * x2) negated.
-	lastApprox := approx.
-	approx := approx + (num / den).
+        facN := facN + 2.
+        den := den * (facN - 1) * facN.
+        num := (num * x2) negated.
+        lastApprox := approx.
+        approx := approx + (num / den).
     ].
     ^ approx
 
     "
      1.0 cos                                    0.540302
+     1.0 asLongFloat cos                        0.5403023058681397174
      1.0 asLongFloat cos_withAccuracy:1         0.5
      1.0 asLongFloat cos_withAccuracy:0.1       0.541666667
      1.0 asLongFloat cos_withAccuracy:0.01      0.540277778
      1.0 asLongFloat cos_withAccuracy:0.001     0.540302579
 
-     1.0 asLongFloat cos_withAccuracy:1e-40     0.540302306
+     1.0 asLongFloat cos_withAccuracy:1e-40     0.5403023058681397175
+     1.0 asQDouble cos                          0.5403023058681396874081335957994
+     1.0 asQDouble cos_withAccuracy:1e-40       
+     Wolfram:
+            0.5403023058681396874081335957994 
+            0.540302305868139717400936607442976603732310420617922227670...
     "
 !
 
@@ -2037,7 +2969,7 @@
 
     |x2 facN num den approx delta|
 
-    x2 := self * self.
+    x2 := self squared.
 
     num := x2.
     den := 2.
@@ -2045,14 +2977,14 @@
     approx := self + (num / den).
 
     [
-	facN := facN + 2.
-	den := den * (facN - 1) * facN.
-	num := num * x2.
-
-	delta := num / den.
-	approx := approx + delta.
+        facN := facN + 2.
+        den := den * (facN - 1) * facN.
+        num := num * x2.
+
+        delta := num / den.
+        approx := approx + delta.
     ] doUntil:[delta <= epsilon].
-    ^ approx
+    ^ approx + self.
 
     "
      1.0 cosh                                    1.54308
@@ -2063,6 +2995,8 @@
 
      1.0q cosh_withAccuracy:1e-40   -> 1.543080
     "
+
+    "Modified: / 01-08-2017 / 14:54:40 / stefan"
 !
 
 epsilon
@@ -2073,7 +3007,9 @@
 !
 
 exp_withAccuracy:epsilon
-    "compute e**x of the receiver using a taylor series approx."
+    "compute e^x of the receiver using a taylor series approximation.
+     This method is only invoked for limitedPrecisionReal classes, which do not compute
+     exp themself (i.e. QDouble)"
 
     "/ uses taylor series:
     "/             x    x^2   x^3
@@ -2082,7 +3018,7 @@
 
     |x2 facN num den approx delta|
 
-    x2 := self * self.
+    x2 := self squared. "/ self squared.
 
     num := x2.
     den := 2.
@@ -2090,18 +3026,26 @@
     approx := self + 1 + (num / den).
 
     [
-	facN := facN + 1.
-	den := den * facN.
-	num := num * self.
-
-	delta := num / den.
-	approx := approx + delta.
+        facN := facN + 1.
+        den := den * facN.
+        num := num * self.
+
+        delta := num / den.
+"/ delta mantissa == 0 ifTrue:[self halt. num / den].
+"/ Transcript showCR:delta.
+        delta isNaN ifTrue:[self halt:'nan when dividing for delta'. num / den].
+        delta = 0 ifTrue:[self halt:'zero delta'].
+        approx := approx + delta.
     ] doUntil:[delta abs <= epsilon].
 
     ^ approx
 
     "
-     -1 exp
+     wolfram:
+                7.389056098930650227230427460575007813180315570551847324087
+
+     (2 asLargeFloat exp_withAccuracy:1e-100) printfPrintString:'%50.48f'                      
+
      1.0 exp                                    2.71828
      1q exp                                     2.71828183
      2q exp                                     7.3890561
@@ -2111,80 +3055,185 @@
      1q exp_withAccuracy:0.01                   2.71666667
      1q exp_withAccuracy:0.001                  2.71825397
 
+     -1 exp                                     0.367879441171442
+     -1q exp_withAccuracy:(1e-60)               0.3678794411714423216
+
      2q exp_withAccuracy:LongFloat epsilon      7.3890561
 
+     42 asQDouble exp_withAccuracy:QDouble epsilon        
+     42 asQDouble exp_withAccuracy:LongFloat epsilon  
+     42 asQDouble exp_withAccuracy:Float epsilon    
+
+     2 asQDouble exp_withAccuracy:QDouble epsilon   7.38905609893065022723     
+     2 asQDouble exp_withAccuracy:LongFloat epsilon 7.38905609893065022723  
+     2 asQDouble exp_withAccuracy:Float epsilon     7.38905609893065022489
+
+     1 asQDouble exp_withAccuracy:QDouble epsilon   2.71828182845904523536     
+     1 asQDouble exp_withAccuracy:LongFloat epsilon 2.71828182845904523536 
+     1 asQDouble exp_withAccuracy:Float epsilon     2.71828182845904522671
+
      1.0 asLongFloat exp_withAccuracy:1e-40     2.71828183
 
      5 exp_withAccuracy:1e-40
      (1 exp_withAccuracy:1e-100) asFixedPoint:100
     "
+
+    "Modified: / 10-10-2017 / 16:04:08 / cg"
 !
 
 ln_withAccuracy:epsilon
     "compute ln of the receiver using a taylor series approx."
 
     "uses taylor series:
-		 u^2   u^3
-	ln = u - --- + --- ...
-		  2    3
+                 u^2   u^3
+        ln = u - --- + --- ...
+                  2    3
       where:
-	     u = x - 1    and: x < 1
-
-     Now we use modified taylor, which converges faster:
-
-		   1+y        1   1       1
-	ln(x) = ln --- = 2y ( - + - y^2 + - y^4 + ....)
-		   1-y        1   3       5
-
-	where y = (x-1) / (x+1)  and x > 0
+             u = x - 1    and: x < 1
+
+     Now we use modified taylor, which converges a little faster:
+
+                   1+y        1   1       1
+        ln(x) = ln --- = 2y ( - + - y^2 + - y^4 + ....)
+                   1-y        1   3       5
+
+        where y = (x-1) / (x+1)  and x > 0
+
+     Warning: this converges very slowly. Find a better algorithm    
     "
 
-    |denominator approx y y2 exp delta|
+    |denominator approx y y2 exp delta count|
 
     self <= 0 ifTrue:[
-	^ self class
-	    raise:#domainErrorSignal
-	    receiver:self
-	    selector:#ln
-	    arguments:#()
-	    errorString:'bad receiver in ln'
+        ^ self class
+            raise:(self = 0 ifTrue:[#infiniteResultSignal] ifFalse:[#domainErrorSignal])
+            receiver:self
+            selector:#ln
+            arguments:#()
+            errorString:'bad receiver in ln (not strictly positive)'
     ].
 
 
     y := (self - 1)/(self + 1).
-    exp := y2 := y * y.
-
-    approx := 1.
-    denominator := 3.
-
+    exp := y2 := y squared.
+
+    approx := 1.0.
+    denominator := 3.0.
+    count := 1.
+    
     [
-	delta := exp / denominator.
-	approx := approx + delta.
-	exp := exp * y2.
-	denominator := denominator + 2.
-    ] doUntil:[delta <= epsilon].
+        delta := exp / denominator.
+        approx := approx + delta.
+        exp := exp * y2.
+        denominator := denominator + 2.
+        
+        count := count + 1.
+        (count \\ 100) == 0 ifTrue:[
+            Logger warning:'slow ln-taylor converging...'.
+        ].    
+    ] doUntil:[delta <= epsilon or:[count > 10000]].
 
     ^ y * 2 * approx.
 
 
     "
-     2.0 ln                         0.693147
-     2.0q ln                        0.693147181
-
-     2.0q ln_withAccuracy:1         0.691358025
-     2.0q ln_withAccuracy:0.1       0.691358025
-     2.0q ln_withAccuracy:0.01      0.693004115
-     2.0q ln_withAccuracy:0.0000001 0.69314718
-
-     2.0q ln_withAccuracy:1e-10
-     2.0q ln_withAccuracy:1e-20
-     2.0q ln_withAccuracy:1e-40     0.693147181
-
-     2 ln_withAccuracy:1e-40
+     2.0 ln                         0.693147180559945
+     2.0q ln                        0.6931471805599453094
+
+     2.0q ln_withAccuracy:1                  0.691358025
+     2.0q ln_withAccuracy:0.1                0.691358025
+     2.0q ln_withAccuracy:0.01               0.693004115
+     2.0q ln_withAccuracy:0.0000001          0.69314718
+     2.0q ln_withAccuracy:1e-10              0.6931471805589163927
+     2.0q ln_withAccuracy:1e-20              0.6931471805599453094
+     2.0q ln_withAccuracy:1e-40              0.6931471805599453094
+     2.0q ln_withAccuracy:2.0q class epsilon 0.6931471805599453094
+
+     (2 ln_withAccuracy:1e-40) -> a fraction        
      0 ln_withAccuracy:1e-40
 
      (2 ln_withAccuracy:1e-100) asFixedPoint:100
+     (2 asFixedPoint:200) ln_withAccuracy:(1/(10 raisedTo:200))
+        0.69314718055994530941723212145817656807550013436025525412068000949339362196969471560586332699641868754200148102057068573368552023575813055703267075163507596193072757082837143519030703862389167347112335
+
+     (2 asFixedPoint:400) ln_withAccuracy:(1/(10 raisedTo:400))
+        0.69314718055994530941723212145817656807550013436025525412068000949339362196969471560586332699641868754200148102057068573368552023575813055703267075163507596193072757082837143519030703862389167347112335 01153644979552391204751726815749320651555247341395258829504530070953263666426541042391578149520437404303855008019441706416715186447128399681717845469570262716310645461502572074024816377733896385506953
+
+     (2.0 asQDouble ln_withAccuracy:QDouble epsilon) printfPrintString:'%60.58f'
+        0.69314718055994 52709398341558750792990469129794959648865081'
+
+     Wolfram says:
+        0.69314718055994530941723212145817656807550013436025525412068000949339362196969471560586332699641868754200148102057068573368552023575813055703267075163507596193072757082837143519030703862389167347112335 01153644979552391204751726...
     "
+
+    "Modified: / 05-07-2017 / 17:16:24 / cg"
+!
+
+nthRoot:n withAccuracy:epsilon
+    "compute nth root of the receiver using a newton approx."
+
+    "
+      Use Newton's method:
+
+                 (n-1)*x_n^n + (a / x_n^(n-1))
+        x_n+1 =  -----------------------------
+                             n
+
+        rt(n, a) = x_n
+    "
+
+    |approx delta absDelta prevDelta|
+
+    self = 0 ifTrue:[
+        ^ self
+    ].
+
+    "/ the demanded epsilon may NEVER be smaller than the real representation's epsilon
+    self assert:(epsilon >= (self class epsilon)).
+    
+    approx := (self / 2).
+    delta := ((self / (approx raisedToInteger:(n-1))) - approx) / n.
+    absDelta := delta abs.
+    approx := approx + delta.
+    
+    [
+        prevDelta := absDelta.
+        
+        delta := ((self / (approx raisedToInteger:(n-1))) - approx) / n.
+        absDelta := delta abs.
+        approx := approx + delta.
+        
+        (absDelta < prevDelta) ifFalse:[ 
+            DomainError raiseRequestErrorString:'no convergence in Newton approx.'
+        ].
+        
+        (absDelta > epsilon)
+    ] whileTrue.
+    ^ approx
+
+    "                                             
+     8q nthRoot:3 withAccuracy:0.01               2.00000002488636242
+     8q nthRoot:3 withAccuracy:0.0001             2.00000000000000031
+     8q nthRoot:3 withAccuracy:0.0000001          2.00000000000000031
+     8q nthRoot:3 withAccuracy:0.0000000001       2.0
+     8q nthRoot:3 withAccuracy:0.000000000001     2.0
+     8q nthRoot:3 withAccuracy:LongFloat epsilon  2.0
+
+     27q nthRoot:3 withAccuracy:0.01                3.000000081210202031
+     27q nthRoot:3 withAccuracy:LongFloat epsilon   3.0
+     -27q nthRoot:3 withAccuracy:LongFloat epsilon  -3.0
+
+     10000q nthRoot:5 withAccuracy:1e-18        -> 6.309573444801932495 
+
+     (10000 asQDouble nthRoot:5) printfPrintString:'%70.68f'
+               6.30957344480193249434360136622343864672945257188228724527729528834741'
+
+     actual result (Mathematica):        
+               6.309573444801932494343601366223438646729452571882287245277...
+    "
+
+    "Created: / 22-06-2017 / 15:51:55 / cg"
+    "Modified: / 22-09-2017 / 10:14:59 / cg"
 !
 
 sin_withAccuracy:epsilon
@@ -2197,7 +3246,7 @@
 
     |x2 facN num den approx delta|
 
-    x2 := self * self.
+    x2 := self squared.
 
     num := (x2 * self) negated.
     den := 2*3.
@@ -2205,12 +3254,12 @@
     approx := self + (num / den).
 
     [
-	facN := facN + 2.
-	den := den * (facN - 1) * facN.
-	num := (num * x2) negated.
-
-	delta := num / den.
-	approx := approx + delta.
+        facN := facN + 2.
+        den := den * (facN - 1) * facN.
+        num := (num * x2) negated.
+
+        delta := num / den.
+        approx := approx + delta.
     ] doUntil:[delta abs <= epsilon].
     ^ approx
 
@@ -2237,7 +3286,7 @@
 
     |x2 facN num den approx delta|
 
-    x2 := self * self.
+    x2 := self squared.
 
     num := x2 * self.
     den := 2*3.
@@ -2245,12 +3294,12 @@
     approx := self + (num / den).
 
     [
-	facN := facN + 2.
-	den := den * (facN - 1) * facN.
-	num := num * x2.
-
-	delta := num / den.
-	approx := approx + delta.
+        facN := facN + 2.
+        den := den * (facN - 1) * facN.
+        num := num * x2.
+
+        delta := num / den.
+        approx := approx + delta.
     ] doUntil:[delta abs <= epsilon].
     ^ approx
 
@@ -2268,38 +3317,82 @@
 !
 
 sqrt_withAccuracy:epsilon
-    "compute square root of the receiver using newtom/heron algorithm"
+    "compute square root of the receiver using newton-raphson/heron algorithm"
+    "Use the Heron algorithm (not Taylor)"
+
+    |guess|
+
+    false "self isInteger" ifTrue:[
+        guess := 1 bitShift:(self highBit // 2)
+    ] ifFalse:[
+        guess := self / 2.0.
+    ].    
+    ^ self sqrt_withAccuracy:epsilon fromInitialGuess:guess
+
     "
-      Use the Heron algorithm:
-
-		 x_n + (a / x_n)
-	x_n+1 =  ---------------
-		      2
-
-	sqrt(a) = x_n
+     2 sqrt                                  1.4142135623731      - computed by CPU/FPU
+     200000000 sqrt                          
+     
+     2q sqrt                                 1.414213562373095049 - computed by CPU/FPU
+
+     2q sqrt_withAccuracy:0.01               1.414215686274509804 - computed by Smalltalk
+     2q sqrt_withAccuracy:0.0001             1.414213562374689911
+     2q sqrt_withAccuracy:0.0000001          1.414213562373095049
+     2q sqrt_withAccuracy:0.0000000001       1.414213562373095049
+     2q sqrt_withAccuracy:0.000000000001     1.414213562373095049
+     
+     2q sqrt_withAccuracy:LongFloat epsilon  1.414213562373095049
+
+     (4 sqrt_withAccuracy:Integer epsilon) asFloat
+
+     MessageTally spyOn:[ |arg|
+        arg := 2 asLongFloat.
+        1000000 timesRepeat:[
+             arg sqrt_withAccuracy:0.000000000001
+        ]
+     ]
+     Time millisecondsToRun:[ |arg|
+        arg := 2 asLongFloat.
+        1000000 timesRepeat:[
+             arg sqrt_withAccuracy:0.000000000001
+        ]
+     ]
     "
 
-    |approx|
+    "Modified: / 25-07-2017 / 17:44:46 / cg"
+!
+
+sqrt_withAccuracy:epsilon fromInitialGuess:guess
+    "compute square root of the receiver using newton-raphson/heron algorithm"
+
+    "Use the Heron algorithm (not Taylor):
+
+                 x_n + (a / x_n)
+        x_n+1 =  ---------------
+                      2
+
+        sqrt(a) = x_n
+    "
+
+    |approx lastApprox|
 
     self <= 0 ifTrue:[
-	self = 0 ifTrue:[
-	    ^ self
-	].
-	^ self class
-	    raise:#imaginaryResultSignal
-	    receiver:self
-	    selector:#sqrt
-	    arguments:#()
-	    errorString:'bad (negative) receiver in sqrt'
+        self = 0 ifTrue:[
+            ^ self
+        ].
+        ^ self class
+            raise:#imaginaryResultSignal
+            receiver:self
+            selector:#sqrt
+            arguments:#()
+            errorString:'bad (negative) receiver in sqrt'
     ].
 
-    approx := 1.
+    approx := guess.
     [
-	|lastApprox|
-
-	lastApprox := approx.
-	approx := ((self / approx) + approx) / 2.
-	(approx - lastApprox) abs > epsilon
+        lastApprox := approx.
+        approx := ((self / approx) + approx) / 2.
+        (approx - lastApprox) abs > epsilon
     ] whileTrue.
     ^ approx
 
@@ -2313,21 +3406,27 @@
      2q sqrt_withAccuracy:0.000000000001     1.414213562373095049
      2q sqrt_withAccuracy:LongFloat epsilon  1.414213562373095049
 
+     (2 asQDouble sqrt_withAccuracy:LongFloat epsilon) printfPrintString:'%70.68f'
+            1.41421356237309504880168872420969807856967187537723400156101313309966
+
      (4 sqrt_withAccuracy:Integer epsilon) asFloat
 
      MessageTally spyOn:[ |arg|
-	arg := 2 asLongFloat.
-	1000000 timesRepeat:[
-	     arg sqrt_withAccuracy:0.000000000001
-	]
+        arg := 2 asLongFloat.
+        1000000 timesRepeat:[
+             arg sqrt_withAccuracy:0.000000000001
+        ]
      ]
      Time millisecondsToRun:[ |arg|
-	arg := 2 asLongFloat.
-	1000000 timesRepeat:[
-	     arg sqrt_withAccuracy:0.000000000001
-	]
+        arg := 2 asLongFloat.
+        1000000 timesRepeat:[
+             arg sqrt_withAccuracy:0.000000000001
+        ]
      ]
     "
+
+    "Created: / 22-06-2017 / 13:59:48 / cg"
+    "Modified (comment): / 25-07-2017 / 16:07:37 / cg"
 !
 
 tan_withAccuracy:epsilon
@@ -2339,7 +3438,7 @@
     "/                 3       15      315      2835                 (2n)!!
     "/ where Bi is the ith bernoulli number.
 
-    |factors idx x2 num t approx lastApprox delta|
+    |factors idx x2 num t approx lastApprox delta nFactors|
 
     "/    (1 to:20) collect:[:n| |num den|
     "/        num := (2 raisedTo:(2*n)) * ((2 raisedTo:(2*n))-1) * ((n*2) bernoulli).
@@ -2347,49 +3446,50 @@
     "/        num / den
     "/    ]
    factors := #(
-	(1 3)
-	(2 15)
-	(17 315)
-	(62 2835)
-	(1382 155925)
-	(21844 6081075)
-	(929569 638512875)
-	(6404582 10854718875)
-	(443861162 1856156927625)
-	(18888466084 194896477400625)
-	(113927491862 2900518163668125)
-	(58870668456604 3698160658676859375)
-	(8374643517010684 1298054391195577640625)
-	(689005380505609448 263505041412702261046875)
-	(129848163681107301953 122529844256906551386796875)
-	(1736640792209901647222 4043484860477916195764296875)
-	(418781231495293038913922 2405873491984360136479756640625)
-	(56518638202982204522669764 801155872830791925447758961328125)
-	(32207686319158956594455462 1126482925555250126673224649609375)).
-
-    x2 := self * self.
-
+        (1 3)
+        (2 15)
+        (17 315)
+        (62 2835)
+        (1382 155925)
+        (21844 6081075)
+        (929569 638512875)
+        (6404582 10854718875)
+        (443861162 1856156927625)
+        (18888466084 194896477400625)
+        (113927491862 2900518163668125)
+        (58870668456604 3698160658676859375)
+        (8374643517010684 1298054391195577640625)
+        (689005380505609448 263505041412702261046875)
+        (129848163681107301953 122529844256906551386796875)
+        (1736640792209901647222 4043484860477916195764296875)
+        (418781231495293038913922 2405873491984360136479756640625)
+        (56518638202982204522669764 801155872830791925447758961328125)
+        (32207686319158956594455462 1126482925555250126673224649609375)).
+
+    nFactors := factors size.
+    x2 := self squared.
     num := x2 * self.               "/ =  x^3
     approx := self + (num / 3).     "/ do the first iteration
     lastApprox := self.
     idx := 2.
     [
-	t := factors at:idx ifAbsent:[].
-	t isNil ifTrue:[
-	    self error:'too many iterations'.
+        idx > nFactors ifTrue:[
+            ArithmeticError raiseErrorString:'too many iterations'.
 "/ Not enough bernoulli numbers for now...
 "/            |tempNum tempDen|
 "/            tempNum := 2 raisedTo:(2*idx).
 "/            tempNum := tempNum * (tempNum-1) * ((2*idx) bernoulli).
 "/            tempDen := (2*idx) factorial.
 "/            t := Array with:tempNum with:tempDen.
-	].
-	idx := idx + 1.
-	num := num * x2.
-
-	delta := num * t first / t second.
-	approx := approx + delta.
-    ] doUntil:[delta abs <= epsilon].
+        ].
+        t := factors at:idx.
+        idx := idx + 1.
+        num := num * x2.
+
+        delta := num * t first / t second.
+        approx := approx + delta.
+        delta abs > epsilon
+    ] whileTrue.
     ^ approx
 
     "
@@ -2404,6 +3504,8 @@
 
      0.5q tan_withAccuracy:1e-40     -- too many iterations
     "
+
+    "Modified: / 15-02-2018 / 18:53:37 / stefan"
 ! !
 
 !Number methodsFor:'testing'!
@@ -2412,20 +3514,30 @@
     "return true if the receiver is divisible by 2."
 
     self fractionPart = 0 ifTrue:[
-	^ (self / 2) fractionPart = 0
+        ^ (self / 2) fractionPart = 0
     ].
 
     "this will raise an error"
     ^ super even
 
     "
-	2 even
-	2.0 even
-	3.0 even
-	2.4 even
-	(5/3) even
-	2 asFraction even
+     2 even
+     2.0 even
+     3.0 even
+     2.4 even
+     (5/3) even
+
+     2 asFraction even
+     (2 asFixedPoint:5) even
+     2 asFloatE even
+     2 asFloatD even
+     2 asFloatQ even
+     2 asFloatQD even
+
+     (2.1 asFloatQD - (QDouble readFrom:'2.1')) fractionPart
     "
+
+    "Modified (comment): / 03-07-2017 / 14:14:46 / cg"
 !
 
 isDivisibleBy:aNumber
@@ -2446,7 +3558,7 @@
 !
 
 isNaN
-    "return true, if the receiver is an invalid float (NaN - not a number)."
+    "return true, if the receiver is an invalid number (NaN - not a number)."
 
     ^ false
 
@@ -2467,14 +3579,20 @@
     ^ self asInteger isPerfectSquare
 
     "
-     0 isPerfectSquare
+     0 isPerfectSquare   
      0.0 isPerfectSquare
+     1 isPerfectSquare  
+     1.0 isPerfectSquare 
+     2 isPerfectSquare  
+     2.0 isPerfectSquare 
      3 isPerfectSquare
      3.0 isPerfectSquare
      4 isPerfectSquare
      4.0 isPerfectSquare
-     9 isPerfectSquare
-     9.0 isPerfectSquare
+     9 isPerfectSquare   
+     9.0 isPerfectSquare  
+     123456789012345678901234567890 squared isPerfectSquare
+     1000 factorial squared isPerfectSquare  
     "
 !
 
@@ -2512,10 +3630,16 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat arcCos.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f arcCos.
+        ].
     ].
     "/ slow fallback
     ^ (self class pi / 2) - self arcSin
+
+    "Modified: / 05-07-2017 / 17:24:32 / cg"
 !
 
 arcCosech
@@ -2526,10 +3650,16 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat arcCosech.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f arcCosech.
+        ].
     ].
     "/ slow fallback
-    ^ ((1 + ((self*self)+1) sqrt) / self) ln
+    ^ ((1 + ((self squared)+1) sqrt) / self) ln
+
+    "Modified: / 05-07-2017 / 17:24:56 / cg"
 !
 
 arcCosh
@@ -2540,10 +3670,16 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat arcCosh.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f arcCosh.
+        ].
     ].
     "/ slow fallback
-    ^ (self + (self*self-1) sqrt) ln.
+    ^ (self + (self squared-1) sqrt) ln.
+
+    "Modified: / 05-07-2017 / 17:25:03 / cg"
 !
 
 arcCoth
@@ -2554,10 +3690,16 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat arcCoth.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f arcCoth.
+        ].
     ].
     "/ slow fallback
     ^ ((self+1) / (self-1)) ln / 2
+
+    "Modified: / 05-07-2017 / 17:25:14 / cg"
 !
 
 arcSech
@@ -2568,10 +3710,16 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat arcSech.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f arcSech.
+        ].
     ].
     "/ slow fallback
-    ^ ((1 + (1-(self*self)) sqrt) / self) ln
+    ^ ((1 + (1-(self squared)) sqrt) / self) ln
+
+    "Modified: / 05-07-2017 / 17:25:22 / cg"
 !
 
 arcSin
@@ -2581,10 +3729,16 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat arcSin.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f arcSin.
+        ].
     ].
     "/ very slow fallback
     ^ self arcSin_withAccuracy:self epsilon
+
+    "Modified: / 05-07-2017 / 17:25:30 / cg"
 !
 
 arcSinh
@@ -2595,11 +3749,17 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat arcSinh.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f arcSinh.
+        ].
     ].
     "/ slow fallback
-    ^ ( self + (self*self+1) sqrt ) ln
-"/    ^ self arcSinh_withAccuracy:self epsilon
+    ^ ( self + (self squared+1) sqrt ) ln
+    "/    ^ self arcSinh_withAccuracy:self epsilon
+
+    "Modified: / 05-07-2017 / 17:25:38 / cg"
 !
 
 arcTan
@@ -2609,10 +3769,16 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat arcTan.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f arcTan.
+        ].
     ].
     "/ very slow fallback
     ^ self arcTan_withAccuracy:self epsilon
+
+    "Modified: / 05-07-2017 / 17:25:46 / cg"
 !
 
 arcTan2:x
@@ -2622,10 +3788,40 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat arcTan2:x.
+        |f|
+
+        (f := self asFloat) isFinite ifTrue:[
+            ^ f arcTan2:x.
+        ].
     ].
     "/ very slow fallback
     ^ self arcTan2_withAccuracy:self epsilon x:x
+
+    "Modified: / 05-07-2017 / 17:26:16 / cg"
+!
+
+arcTan:denominator
+    "Evaluate the four quadrant arc tangent of the argument denominator (x) and the receiver (y)."
+
+    |t|
+    
+    (self isZero) ifTrue: [
+        (denominator strictlyPositive)
+            ifTrue: [ ^ 0 ]
+            ifFalse: [ ^ self class pi ]
+    ].
+    (denominator isZero) ifTrue: [
+        (self strictlyPositive)
+            ifTrue: [ ^ self class halfpi ]
+            ifFalse: [ ^ self class halfpiNegative ]
+    ].
+    t := (self / denominator) arcTan.
+    (denominator strictlyPositive)
+        ifTrue: [ ^ t ]
+        ifFalse: [ ^ t + self class pi ]
+
+    "Created: / 07-06-2007 / 21:10:32 / cg"
+    "Modified: / 11-06-2007 / 12:58:34 / cg"
 !
 
 arcTanh
@@ -2636,11 +3832,17 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat arcTanh.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f arcTanh.
+        ].
     ].
     "/ slow fallback
     ^ ((1 + self) / (1 - self)) ln / 2
     "/ s^ ((1 + self) ln / 2) - ((1 - self) ln / 2)
+
+    "Modified: / 05-07-2017 / 17:26:27 / cg"
 !
 
 cos
@@ -2650,10 +3852,16 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat cos.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f cos.
+        ].
     ].
     "/ very slow fallback
     ^ self cos_withAccuracy:self epsilon
+
+    "Modified: / 05-07-2017 / 17:26:33 / cg"
 !
 
 cosh
@@ -2663,10 +3871,16 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat cosh.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f cosh.
+        ].
     ].
     "/ very slow fallback
     ^ self cosh_withAccuracy:self epsilon
+
+    "Modified: / 05-07-2017 / 17:26:39 / cg"
 !
 
 cot
@@ -2675,6 +3889,18 @@
     ^ 1 / self tan
 !
 
+csc
+    "return the cosecant of the receiver (interpreted as radians)"
+
+    ^ 1 / self sin
+!
+
+sec
+    "return the secant of the receiver (interpreted as radians)"
+
+    ^ 1 / self cos
+!
+
 sin
     "return the sine of the receiver (interpreted as radians)"
 
@@ -2682,9 +3908,15 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat sin.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f sin.
+        ].
     ].
     ^ self sin_withAccuracy:self epsilon
+
+    "Modified: / 05-07-2017 / 17:26:47 / cg"
 !
 
 sinh
@@ -2694,9 +3926,20 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat sinh.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f sinh.
+        ].
     ].
     ^ self sinh_withAccuracy:self epsilon
+
+    "
+        10 sinh                     -> 11013.23287470339338
+        (10 exp - (-10 exp)) / 2    -> 11013.23287470339338
+    "
+
+    "Modified (comment): / 05-07-2017 / 17:32:27 / cg"
 !
 
 tan
@@ -2709,33 +3952,61 @@
 tanh
     "return the hyperbolic tangens of the receiver"
 
+    "/ tanh is:
+    "/      sinh(x)
+    "/      -------
+    "/      cosh(x)
+    "/
+    "/ which is:
+    "/      (exp(x) - exp(-x)) / 2
+    "/      ----------------------
+    "/      (exp(x) + exp(-x)) / 2
+
+    |exp nexp|
+    
     "/ if I am not a Float (or a less general lpReal),
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-	^ self asFloat tanh.
+        |f|
+
+        (f := self asLongFloat) isFinite ifTrue:[
+            ^ f tanh.
+        ].
     ].
+
     "/ very slow fallback
-    ^ self tanh_withAccuracy:self epsilon
-
-"/ If a fast exp is available, the following might be better...
-"/
-"/    |exp nexp|
-"/
-"/    "/ tanh is:
-"/    "/      sinh(x)
-"/    "/      -------
-"/    "/      cosh(x)
-"/    "/
-"/    "/ which is:
-"/    "/      (exp(x) - exp(-x)) / 2
-"/    "/      ----------------------
-"/    "/      (exp(x) + exp(-x)) / 2
-"/
-"/    exp := self exp.
-"/    nexp := self negated exp.
-"/
-"/    ^ (exp - nexp) / (exp + nexp)
+    "/ assuming that if we arrive here, the stuff is taylor computed manually anyway,
+    "/ the question is if taylor-for-exp converges faster than tailor-for-sin/cos
+    "/ So it may be faster to:
+    "/      ^ self sinh / self cosh
+    
+    exp := self exp.
+    nexp := self negated exp.
+
+    ^ (exp - nexp) / (exp + nexp)
+
+    "Modified (comment): / 05-07-2017 / 17:34:59 / cg"
+! !
+
+!Number methodsFor:'trigonometric (degrees)'!
+
+degreeCos
+    "Return the cosine of the receiver taken as an angle in degrees."
+
+    ^ self degreesToRadians cos
+!
+
+degreeSin
+    "Return the sine of the receiver taken as an angle in degrees."
+
+    ^ self degreesToRadians sin
+!
+
+degreeTan
+    "Return the cosine of the receiver taken as an angle in degrees."
+
+    ^ self degreesToRadians tan
 ! !
 
 !Number methodsFor:'truncation & rounding'!
@@ -2771,18 +4042,25 @@
 !
 
 fractionPart
-    "return a float with value from digits after the decimal point.
+    "return a number with value from digits after the decimal point.
      i.e. the receiver minus its truncated value,
-     such that (self truncated + self fractionPart) = self"
+     such that (self truncated + self fractionPart) = self
+     Floats will return an inexact float; fractions will return a fraction"
 
     ^ self - self truncated
 
     "
-     1234.56789 fractionPart
-     1.2345e6 fractionPart
-
-     1.6 asLongFloat fractionPart + 1.6 asLongFloat truncated
-     -1.6 asLongFloat fractionPart + -1.6 asLongFloat truncated
+     1234.56789 fractionPart -- beware rounding errors in floats
+     1.2345e0 fractionPart    
+     1.2345e1 fractionPart  
+     1.2345e6 fractionPart  
+     (16/10) fractionPart    
+     (8/9) fractionPart    
+     (11/9) fractionPart    
+
+     1.6 asLongFloat fractionPart + 1.6 asLongFloat truncated  -- beware rounding errors in floats 
+     -1.6 asLongFloat fractionPart + -1.6 asLongFloat truncated -1.600000000000000089
+     (16/10) fractionPart + (16/10) truncated -> 16/10
     "
 
     "Modified: / 4.11.1996 / 20:26:54 / cg"
@@ -2790,27 +4068,29 @@
 !
 
 integerPart
-    "return a float with value from digits before the decimal point
-     (i.e. the truncated value)"
-
-    ^ self truncated asFloat
+    "return a number with value from digits before the decimal point.
+     (i.e. the value truncated towards zero)
+     such that (self integerPart + self fractionPart) = self
+     Floats will return an inexact float; fractions will return an exact integer.
+     "
+
+    ^ self truncated
 
     "
-     1234.56789 integerPart
+     1234.56789 integerPart  
      1.2345e6 integerPart
      12.5 integerPart
      -12.5 integerPart
      (5/3) integerPart
      (-5/3) integerPart
-     (5/3) truncated
-     (-5/3) truncated
+     (5/3) truncated        
+     (-5/3) truncated 
     "
 
     "Created: / 28.10.1998 / 17:14:56 / cg"
     "Modified: / 5.11.2001 / 17:54:22 / cg"
 ! !
 
-
 !Number class methodsFor:'documentation'!
 
 version