Number.st
changeset 20308 9110f117d260
parent 20142 c1ec3253b3c1
child 20331 f9e364521eda
child 20344 152b525b5c63
--- a/Number.st	Fri Aug 26 01:12:20 2016 +0200
+++ b/Number.st	Fri Aug 26 12:15:15 2016 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -26,7 +26,7 @@
 copyright
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -42,23 +42,23 @@
     abstract superclass for all kinds of numbers
 
     [class variables:]
-        DecimalPointCharacterForPrinting          <Character>                     used when printing
-        DecimalPointCharactersForReading          <Collection of Character>       accepted as decimalPointChars when reading
-
-        DefaultDisplayRadix     the radix in which integers present their
-                                displayString (which is used in inspectors)
-                                If you are to look at many hex numbers, bitmasks
-                                etc. you may set this to 2 or 16.
-                                (avoids typing printStringRadix:.. all the time
-                                 - I know - I am lazy ;-). Default is 10.
-        
+	DecimalPointCharacterForPrinting          <Character>                     used when printing
+	DecimalPointCharactersForReading          <Collection of Character>       accepted as decimalPointChars when reading
+
+	DefaultDisplayRadix     the radix in which integers present their
+				displayString (which is used in inspectors)
+				If you are to look at many hex numbers, bitmasks
+				etc. you may set this to 2 or 16.
+				(avoids typing printStringRadix:.. all the time
+				 - I know - I am lazy ;-). Default is 10.
+
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [see also:]
-        Integer LargeInteger SmallInteger
-        LimitedPrecisionReal Float ShortFloat
-        Fraction FixedPoint
+	Integer LargeInteger SmallInteger
+	LimitedPrecisionReal Float ShortFloat
+	Fraction FixedPoint
 "
 ! !
 
@@ -85,18 +85,18 @@
      should be roughly 10times faster than the general method:
 
      Time millisecondsToRun:[
-        100000 timesRepeat:[ Float fromString:'12345.0' ]
-     ].   
+	100000 timesRepeat:[ Float fromString:'12345.0' ]
+     ].
      Time millisecondsToRun:[
-        100000 timesRepeat:[ Float fastFromString:'12345.0' ]
-     ].   
+	100000 timesRepeat:[ Float fastFromString:'12345.0' ]
+     ].
 
      Time millisecondsToRun:[
-        100000 timesRepeat:[ Integer fromString:'12345' ]
-     ].  
+	100000 timesRepeat:[ Integer fromString:'12345' ]
+     ].
      Time millisecondsToRun:[
-        100000 timesRepeat:[ Integer fastFromString:'12345' ]
-     ]. 
+	100000 timesRepeat:[ Integer fastFromString:'12345' ]
+     ].
     "
 !
 
@@ -106,19 +106,19 @@
      I.e. the string must contain exactly one valid number (with optional separators around)"
 
     ^ self
-        fromString:aString
-        decimalPointCharacters:(self decimalPointCharactersForReading) 
+	fromString:aString
+	decimalPointCharacters:(self decimalPointCharactersForReading)
 
     "
      Number fromString:'12345'
      Number fromString:'abc'
      Number fromString:'1abc'   -> raises an error
-     Number readFrom:'1abc'     -> reads a 1    
-     Number readFrom:'10/2'     -> reads a 10   
-     Number fromString:'10/2'   -> raises an error   
-     Number fromString:'(1/2)'  -> reads a fraction   
-     Number readFrom:'(1/2)'    -> reads a fraction   
-     Number readFrom:'(10/2)'   -> reads a 5   
+     Number readFrom:'1abc'     -> reads a 1
+     Number readFrom:'10/2'     -> reads a 10
+     Number fromString:'10/2'   -> raises an error
+     Number fromString:'(1/2)'  -> reads a fraction
+     Number readFrom:'(1/2)'    -> reads a fraction
+     Number readFrom:'(10/2)'   -> reads a 5
      '12345' asNumber
     "
 
@@ -135,10 +135,10 @@
     s := aString readStream.
     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.
 
@@ -182,7 +182,7 @@
     "Modified: / 3.8.1998 / 20:05:34 / cg"
 !
 
-readFrom:aStringOrStream decimalPointCharacters:decimalPointCharacters 
+readFrom:aStringOrStream decimalPointCharacters:decimalPointCharacters
     "return the next Number from the (character-)stream aStream;
      skipping all whitespace first.
      Return the value of exceptionBlock, if no number can be read.
@@ -192,14 +192,14 @@
      See #fromString: , which is more strict and does not allow garbage at the end."
 
     ^ self
-        readFrom:aStringOrStream 
-        decimalPointCharacters:decimalPointCharacters 
-        onError:[self error:'conversion error for: ' , self name]
+	readFrom:aStringOrStream
+	decimalPointCharacters:decimalPointCharacters
+	onError:[self error:'conversion error for: ' , self name]
 
     "
-     Number readFrom:'123.456' decimalPointCharacters:'.'      
-     Number readFrom:'123,456' decimalPointCharacters:'.,'     
-     Number readFrom:'123,456' decimalPointCharacters:'.'     
+     Number readFrom:'123.456' decimalPointCharacters:'.'
+     Number readFrom:'123,456' decimalPointCharacters:'.,'
+     Number readFrom:'123,456' decimalPointCharacters:'.'
     "
 !
 
@@ -213,177 +213,177 @@
      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 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.
+	].
+	(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.
+		].
+		(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
 
     "
-     Number readFrom:(ReadStream on:'54.32e-01')      
-     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:'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:(ReadStream on:'54.32e-01')
+     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:'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'      
+     Number fromString:'123garbage'    -> raises an error
+
+     DecimalPointCharactersForReading := #( $. $, ).
+     Number readFrom:'99,00'
+
+     DecimalPointCharactersForReading := #( $. ).
+     Number readFrom:'99,00'
     "
 
     "Modified: / 14.4.1998 / 19:22:50 / cg"
@@ -398,77 +398,77 @@
      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:(self decimalPointCharactersForReading) 
-        onError:exceptionBlock
+    ^ self
+	readFrom:aStringOrStream
+	decimalPointCharacters:(self decimalPointCharactersForReading)
+	onError:exceptionBlock
 
     "
-     Number readFrom:(ReadStream on:'54.32e-01')      
-     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:'0.000001'  
-     '+00000123.45' asNumber  
-     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'      
-
-     DecimalPointCharactersForReading := #( $. $, ).   
-     Number readFrom:'99,00'      
-
-     DecimalPointCharactersForReading := #( $. ).   
-     Number readFrom:'99,00'      
+     Number readFrom:(ReadStream on:'54.32e-01')
+     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:'0.000001'
+     '+00000123.45' asNumber
+     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'
+
+     DecimalPointCharactersForReading := #( $. $, ).
+     Number readFrom:'99,00'
+
+     DecimalPointCharactersForReading := #( $. ).
+     Number readFrom:'99,00'
     "
 !
 
 readSmalltalkSyntaxFrom:aStream
     "ST-80 compatibility (thanks to a note from alpha testers)
-     read and return the next Number in smalltalk syntax from the 
+     read and return the next Number in smalltalk syntax from the
      (character-) aStream.
      Returns nil if aStream contains no valid number."
 
     ^ self readSmalltalkSyntaxFrom:aStream onError:nil.
 
     "
-     Number readSmalltalkSyntaxFrom:'99d'    
-     Number readSmalltalkSyntaxFrom:'99.00d'    
-     Number readSmalltalkSyntaxFrom:'54.32e-01'    
+     Number readSmalltalkSyntaxFrom:'99d'
+     Number readSmalltalkSyntaxFrom:'99.00d'
+     Number readSmalltalkSyntaxFrom:'54.32e-01'
      Number readSmalltalkSyntaxFrom:'12345678901234567890'
-     Number readSmalltalkSyntaxFrom:'16rAAAAFFFFAAAAFFFF'   
-     Number readSmalltalkSyntaxFrom:'foobar'     
-     Number readSmalltalkSyntaxFrom:'(1/10)' 
-
-     Number readSmalltalkSyntaxFrom:'(1/0)' 
-
-     Number readFrom:'(1/3)' 
+     Number readSmalltalkSyntaxFrom:'16rAAAAFFFFAAAAFFFF'
+     Number readSmalltalkSyntaxFrom:'foobar'
+     Number readSmalltalkSyntaxFrom:'(1/10)'
+
+     Number readSmalltalkSyntaxFrom:'(1/0)'
+
+     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 readSmalltalkSyntaxFrom:'+00000123.45'  
-     Number readFrom:'+00000123.45'  
+     Number readFrom:'-(1/3)'
+     Number readFrom:'(1/-3)'
+     Number readFrom:'(-1/-3)'
+     Number readFrom:'-(-1/-3)'
+     Number readSmalltalkSyntaxFrom:'+00000123.45'
+     Number readFrom:'+00000123.45'
 
      |s|
      s := ReadStream on:'2.'.
      Number readSmalltalkSyntaxFrom:s.
-     s next    
+     s next
 
      |s|
      s := ReadStream on:'2.0.'.
      Number readSmalltalkSyntaxFrom:s.
-     s next    
+     s next
     "
 
     "Modified: / 19.11.1999 / 18:26:47 / cg"
@@ -476,22 +476,22 @@
 
 readSmalltalkSyntaxFrom:aStream onError:errorValue
     "ST-80 compatibility (thanks to a note from alpha testers)
-     read and return the next Number in smalltalk syntax from the 
+     read and return the next Number in smalltalk syntax from the
      (character-) aStream.
      Returns nil if aStream contains no valid number."
 
     |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:'foo' onError:123
     "
 ! !
 
@@ -506,7 +506,7 @@
 
 !Number class methodsFor:'constants'!
 
-decimalPointCharacter 
+decimalPointCharacter
     "printed"
 
     <resource: #obsolete>
@@ -514,7 +514,7 @@
     ^ self decimalPointCharacterForPrinting
 !
 
-decimalPointCharacter:aCharacter 
+decimalPointCharacter:aCharacter
     "printed"
 
     <resource: #obsolete>
@@ -525,18 +525,18 @@
      1.5 printString
 
      Number decimalPointCharacter:$,.
-     1.5 printString       
+     1.5 printString
      Number decimalPointCharacter:$..
     "
 !
 
-decimalPointCharacterForPrinting 
+decimalPointCharacterForPrinting
     "printed"
 
     ^ DecimalPointCharacterForPrinting ? $.
 !
 
-decimalPointCharacterForPrinting:aCharacter 
+decimalPointCharacterForPrinting:aCharacter
     "printed"
 
     DecimalPointCharacterForPrinting := aCharacter
@@ -545,12 +545,12 @@
      1.5 printString
 
      Number decimalPointCharacterForPrinting:$,.
-     1.5 printString       
+     1.5 printString
      Number decimalPointCharacterForPrinting:$..
     "
 !
 
-decimalPointCharacters 
+decimalPointCharacters
     "accepted when converting from a string"
 
     <resource: #obsolete>
@@ -561,28 +561,28 @@
      1.5 printString
 
      Number decimalPointCharacters:#( $. $,) .
-     Number fromString:'1.5'.     
-     Number fromString:'1,5'.     
+     Number fromString:'1.5'.
+     Number fromString:'1,5'.
      Number decimalPointCharacters:#( $. ).
     "
 !
 
-decimalPointCharacters:aCollectionOfCharacters 
+decimalPointCharacters:aCollectionOfCharacters
     "accepted when converting from a string"
 
     <resource: #obsolete>
 
-    self decimalPointCharactersForReading:aCollectionOfCharacters 
+    self decimalPointCharactersForReading:aCollectionOfCharacters
 
     "
      Number decimalPointCharacters:#( $. $,) .
-     Number fromString:'1.5'.     
-     Number fromString:'1,5'.     
+     Number fromString:'1.5'.
+     Number fromString:'1,5'.
      Number decimalPointCharacters:#( $. ).
     "
 !
 
-decimalPointCharactersForReading 
+decimalPointCharactersForReading
     "default when converting from a string"
 
     "/ cg: changing the default leads to trouble in some
@@ -590,7 +590,7 @@
     "/ PLEASE DO ONLY CHANGE THE DEFAULT BELOW FOR END-USER APPLICATIONS (if at all).
     "/ BETTER: pass the DecimalPointCharacterSet explicitly
     DecimalPointCharactersForReading isNil ifTrue:[
-        ^ #( $. )
+	^ #( $. )
     ].
     ^ DecimalPointCharactersForReading
 
@@ -598,27 +598,27 @@
      1.5 printString
 
      Number decimalPointCharactersForReading:#( $. $,) .
-     Number fromString:'1.5'.     
-     Number fromString:'1,5'.     
+     Number fromString:'1.5'.
+     Number fromString:'1,5'.
      Number decimalPointCharactersForReading:#( $. ).
     "
 !
 
-decimalPointCharactersForReading:aCollectionOfCharacters 
+decimalPointCharactersForReading:aCollectionOfCharacters
     "accepted when converting from a string"
 
     DecimalPointCharactersForReading := aCollectionOfCharacters
 
     "
      Number decimalPointCharactersForReading:#( $. $,) .
-     Number fromString:'1.5'.     
-     Number fromString:'1,5'.     
+     Number fromString:'1.5'.
+     Number fromString:'1,5'.
      Number decimalPointCharactersForReading:#( $. ).
     "
 !
 
 epsilon
-    "return the maximum relative spacing of instances of mySelf 
+    "return the maximum relative spacing of instances of mySelf
      (i.e. the value-delta of the least significant bit)"
 
      ^ self subclassResponsibility
@@ -632,9 +632,9 @@
     ^ 0.0001
 
     "
-     Float epsilon     
-     ShortFloat epsilon 
-     Float epsilon10    
+     Float epsilon
+     ShortFloat epsilon
+     Float epsilon10
      ShortFloat epsilon10
     "
 !
@@ -647,31 +647,31 @@
 
 !Number class methodsFor:'error reporting'!
 
-raise:aSignalSymbolOrErrorClass receiver:someNumber selector:sel arg:arg errorString:text 
+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 
+	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'
+     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 
+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."
@@ -679,18 +679,18 @@
     <context: #return>
 
     ^ self
-        raise:aSignalSymbolOrErrorClass 
-        receiver:someNumber 
-        selector:sel 
-        arguments:#()
-        errorString:text 
+	raise:aSignalSymbolOrErrorClass
+	receiver:someNumber
+	selector:sel
+	arguments:#()
+	errorString:text
 
     "
-     Number 
-        raise:#domainErrorSignal
-        receiver:1.0
-        selector:#foo 
-        errorString:'foo bar test'
+     Number
+	raise:#domainErrorSignal
+	receiver:1.0
+	selector:#foo
+	errorString:'foo bar test'
     "
 
     "Modified: / 16.11.2001 / 14:13:16 / cg"
@@ -717,7 +717,7 @@
 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 
+     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."
@@ -730,29 +730,29 @@
     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
+	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. 
+     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"
@@ -799,8 +799,8 @@
     ^ pos
 
     "
-     #(-500 -300 -150 -5 0 5 150 300 500 1200) 
-        collect: [:n | n asSmallAngleDegrees]
+     #(-500 -300 -150 -5 0 5 150 300 500 1200)
+	collect: [:n | n asSmallAngleDegrees]
     "
 !
 
@@ -810,17 +810,17 @@
     ^ self closeFrom:aNumber withEpsilon:(self class epsilonForCloseTo)
 
     "
-     9.0 closeTo: 8.9999     
-     9.9 closeTo: 9          
-     (9/3) closeTo: 2.9999      
-     1 closeTo: 0.9999      
-     1 closeTo: 1.0001      
-     1 closeTo: 1.001       
-     1 closeTo: 0.999       
-
-     0.9999 closeTo: 1      
-     1.0001 closeTo: 1      
-     1.001 closeTo: 1     
+     9.0 closeTo: 8.9999
+     9.9 closeTo: 9
+     (9/3) closeTo: 2.9999
+     1 closeTo: 0.9999
+     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
@@ -832,24 +832,24 @@
 
     | fuzz |
 
-    self isNaN == aNumber isNaN ifFalse: [^ false]. 
+    self isNaN == aNumber isNaN ifFalse: [^ false].
     self isInfinite == aNumber isInfinite ifFalse: [^ false].
 
-    fuzz := (self abs max:aNumber abs) * eps. 
+    fuzz := (self abs max:aNumber abs) * eps.
     ^ (self - aNumber) abs <= fuzz
 
     "
-     9.0 closeTo: 8.9999     
-     9.9 closeTo: 9          
-     (9/3) closeTo: 2.9999      
-     1 closeTo: 0.9999      
-     1 closeTo: 1.0001      
-     1 closeTo: 1.001       
-     1 closeTo: 0.999       
-
-     0.9999 closeTo: 1      
-     1.0001 closeTo: 1      
-     1.001 closeTo: 1     
+     9.0 closeTo: 8.9999
+     9.9 closeTo: 9
+     (9/3) closeTo: 2.9999
+     1 closeTo: 0.9999
+     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
@@ -862,7 +862,7 @@
     ^ self closeTo:num withEpsilon:(self class epsilonForCloseTo)
 
     "
-     1 closeTo:1.0000000001 
+     1 closeTo:1.0000000001
      1 closeTo:1.001
      1 closeTo:1.001 withEpsilon:0.001
     "
@@ -877,11 +877,11 @@
     ^ num closeFrom:self withEpsilon:eps
 
     "
-     1 closeTo:1.0000000001        
-     1 closeTo:1.001               
-
-     1 closeTo:1.001 withEpsilon:0.1 
-     1 closeTo:1.201 withEpsilon:0.1 
+     1 closeTo:1.0000000001
+     1 closeTo:1.001
+
+     1 closeTo:1.001 withEpsilon:0.1
+     1 closeTo:1.201 withEpsilon:0.1
 
      3.14 closeTo:(3.14 asFixedPoint:2)
      (3.14 asFixedPoint:2) closeTo:3.14
@@ -893,24 +893,24 @@
 
 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
+isEqual: aNumber within: accuracy
+	^(self - aNumber) abs < accuracy
 !
 
 rounded:n
@@ -922,13 +922,13 @@
     ^ (((self * mult) rounded) asFloat / mult).
 
     "
-     7 rounded:2   
-     7.1 rounded:2    
-     7.2345 rounded:2 
-     7.2385 rounded:2 
-     7.2341 rounded:3   
-     7.2345 rounded:3   
-     7.2348 rounded:3   
+     7 rounded:2
+     7.1 rounded:2
+     7.2345 rounded:2
+     7.2385 rounded:2
+     7.2341 rounded:3
+     7.2345 rounded:3
+     7.2348 rounded:3
     "
 !
 
@@ -944,25 +944,25 @@
     "return a complex number, with the receiver as imaginary part, 0 as real part"
 
     ^ Complex
-        real:0
-        imaginary:self
+	real:0
+	imaginary:self
 
     "
-     3i          
-     (1+1i)      
+     3i
+     (1+1i)
     "
 ! !
 
 !Number methodsFor:'comparing'!
 
-isAlmostEqualTo:aNumber nEpsilon:nE 
+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.
 
-     For background information why floats need this 
+     For background information why floats need this
      read: http://randomascii.wordpress.com/2012/02/25/comparing-floating-point-numbers-2012-edition/
     "
 
@@ -973,21 +973,21 @@
     scaledEpsilon := nE * diff class epsilon.
 
     diff <= scaledEpsilon ifTrue:[
-        "compare for really close values near 0"
-        ^ true.
+	"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)).
+	"scaled comparison for larger values"
+	f1 := self abs.
+	f2 := aNumber abs.
+	largest := f1 > f2 ifTrue:[f1] ifFalse:[f2].
+	^ (diff <= (scaledEpsilon * largest)).
     ].
 ! !
 
 !Number methodsFor:'converting'!
 
-% aNumber 
-    "Return a complex number with the receiver as the real part and 
+% aNumber
+    "Return a complex number with the receiver as the real part and
      aNumber as the imaginary part"
 
     ^ Complex real:self imaginary:aNumber
@@ -1001,10 +1001,10 @@
     ^ MeasurementValue value:self minValue:(self-anError) maxValue:(self+anError)
 
     "
-     (100 +/- 5) * 2            
-     (100 +/- 5) * (100 +/- 10)  
-     (100 +/- 5) + (100 +/- 10)  
-     (100 +/- 5) - (100 +/- 10)  
+     (100 +/- 5) * 2
+     (100 +/- 5) * (100 +/- 10)
+     (100 +/- 5) + (100 +/- 10)
+     (100 +/- 5) - (100 +/- 10)
     "
 
     "Modified (comment): / 14-02-2012 / 14:17:36 / cg"
@@ -1020,20 +1020,20 @@
      * I cannot tell if this special code is worth anything
      */
     if (__CanDoQuickNew(sizeof(struct __Point))) {      /* OBJECT ALLOCATION */
-        OBJ newPoint;
-        int spc;
-
-        __qCheckedAlignedNew(newPoint, sizeof(struct __Point));
-        __InstPtr(newPoint)->o_class = @global(Point);
-        __qSTORE(newPoint, @global(Point));
-        __PointInstPtr(newPoint)->p_x = self;
-        __PointInstPtr(newPoint)->p_y = aNumber;
-        if (! __bothSmallInteger(self, aNumber)) {
-            spc = __qSpace(newPoint);
-            __STORE_SPC(newPoint, aNumber, spc);
-            __STORE_SPC(newPoint, self, spc);
-        }
-        RETURN ( newPoint );
+	OBJ newPoint;
+	int spc;
+
+	__qCheckedNew(newPoint, sizeof(struct __Point));
+	__InstPtr(newPoint)->o_class = @global(Point);
+	__qSTORE(newPoint, @global(Point));
+	__PointInstPtr(newPoint)->p_x = self;
+	__PointInstPtr(newPoint)->p_y = aNumber;
+	if (! __bothSmallInteger(self, aNumber)) {
+	    spc = __qSpace(newPoint);
+	    __STORE_SPC(newPoint, aNumber, spc);
+	    __STORE_SPC(newPoint, self, spc);
+	}
+	RETURN ( newPoint );
     }
 %}
 .
@@ -1041,7 +1041,7 @@
 !
 
 asComplex
-    "Return a complex number with the receiver as the real part and 
+    "Return a complex number with the receiver as the real part and
      zero as the imaginary part"
 
     ^ Complex real:self
@@ -1062,7 +1062,7 @@
 asPercentFrom:fullAmount
     "what is the percentage
      taking the receiver's value from the argument"
-    
+
     ^ (self / fullAmount) * 100.
 
     "
@@ -1073,22 +1073,22 @@
 !
 
 asPoint
-    "return a new Point with the receiver as all coordinates;  
-     often used to supply the same value in two dimensions, as with 
+    "return a new Point with the receiver as all coordinates;
+     often used to supply the same value in two dimensions, as with
      symmetrical gridding or scaling."
 
 %{  /* NOCONTEXT */
 
     if (__CanDoQuickNew(sizeof(struct __Point))) {      /* OBJECT ALLOCATION */
-        OBJ newPoint;
-
-        __qCheckedAlignedNew(newPoint, sizeof(struct __Point));
-        __InstPtr(newPoint)->o_class = @global(Point);
-        __qSTORE(newPoint, @global(Point));
-        __PointInstPtr(newPoint)->p_x = self;
-        __PointInstPtr(newPoint)->p_y = self;
-        __STORE(newPoint, self);
-        RETURN ( newPoint );
+	OBJ newPoint;
+
+	__qCheckedNew(newPoint, sizeof(struct __Point));
+	__InstPtr(newPoint)->o_class = @global(Point);
+	__qSTORE(newPoint, @global(Point));
+	__PointInstPtr(newPoint)->p_x = self;
+	__PointInstPtr(newPoint)->p_y = self;
+	__STORE(newPoint, self);
+	RETURN ( newPoint );
     }
 %}.
     ^ Point x:self y:self
@@ -1098,12 +1098,12 @@
     "return an TimeDuration object from the receiver, taking the receiver
      as number of seconds"
 
-    ^ TimeDuration seconds:self 
+    ^ TimeDuration seconds:self
 
     "
-     5 asTimeDuration   
-     50.25 asTimeDuration 
-     3600 asTimeDuration 
+     5 asTimeDuration
+     50.25 asTimeDuration
+     3600 asTimeDuration
     "
 
     "Created: / 08-01-2012 / 19:04:04 / cg"
@@ -1132,7 +1132,7 @@
 
 percentOf:hundredPercent
     "how many is self-percent from the argument"
-    
+
     ^ (hundredPercent / 100 * self)
 
     "
@@ -1148,22 +1148,22 @@
     ^ self * (180.0 / Float pi)
 
     "
-     180 degreesToRadians     
+     180 degreesToRadians
      Float pi radiansToDegrees
     "
 !
 
 withScale:newScale
-    "return a fixedPoint number representing the same value as the receiver, 
+    "return a fixedPoint number representing the same value as the receiver,
      with newScale number of post-decimal digits"
 
     ^ self asFixedPoint:newScale
 
     "
-     1234 withScale:2 
-     1234.1 withScale:2 
-     1234.12 withScale:2 
-     1234.123 withScale:2 
+     1234 withScale:2
+     1234.1 withScale:2
+     1234.12 withScale:2
+     1234.123 withScale:2
      (1/7) withScale:2
     "
 ! !
@@ -1176,10 +1176,10 @@
     ^ TimeDuration days:self
 
     "
-     1000 milliseconds 
-     10 seconds 
-     10 minutes 
-     1 days 
+     1000 milliseconds
+     10 seconds
+     10 minutes
+     1 days
     "
 !
 
@@ -1189,9 +1189,9 @@
     ^ TimeDuration hours:self
 
     "
-     1000 milliseconds 
-     10 seconds 
-     10 minutes 
+     1000 milliseconds
+     10 seconds
+     10 minutes
     "
 !
 
@@ -1201,7 +1201,7 @@
     ^ TimeDuration fromMilliseconds:self
 
     "
-     1000 milliseconds 
+     1000 milliseconds
     "
 !
 
@@ -1211,9 +1211,9 @@
     ^ TimeDuration minutes:self
 
     "
-     1000 milliseconds 
-     10 seconds 
-     10 minutes 
+     1000 milliseconds
+     10 seconds
+     10 minutes
     "
 !
 
@@ -1223,9 +1223,9 @@
     ^ TimeDuration seconds:self
 
     "
-     1000 milliseconds 
-     10 seconds      
-     10 minutes      
+     1000 milliseconds
+     10 seconds
+     10 minutes
     "
 !
 
@@ -1235,11 +1235,11 @@
     ^ TimeDuration weeks:self
 
     "
-     1000 milliseconds 
-     10 seconds 
-     10 minutes 
-     1 days 
-     1 weeks 
+     1000 milliseconds
+     10 seconds
+     10 minutes
+     1 days
+     1 weeks
     "
 
     "Created: / 05-09-2011 / 11:17:59 / cg"
@@ -1254,10 +1254,10 @@
     ^ aTimestamp subtractMilliseconds:(self * 1000) truncated.
 
     "
-     100.0 differenceFromTimestamp:Timestamp now 
+     100.0 differenceFromTimestamp:Timestamp now
 
      |t1 t2|
-     t1 := Timestamp now. 
+     t1 := Timestamp now.
      t2 := 1.5 differenceFromTimestamp:t1.
      t1 inspect. t2 inspect.
     "
@@ -1307,7 +1307,7 @@
 
     "
      (1 to:256 byFactor:2)
-     (256 to:1 byFactor:1/2)     
+     (256 to:1 byFactor:1/2)
     "
 ! !
 
@@ -1320,8 +1320,8 @@
 
     count := self.
     [count > 0] whileTrue:[
-        aBlock value.
-        count := count - 1
+	aBlock value.
+	count := count - 1
     ]
 ! !
 
@@ -1334,7 +1334,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat cbrt.
+	^ self asFloat cbrt.
     ].
     "/ very slow fallback
     ^ self cbrt_withAccuracy:self epsilon
@@ -1355,7 +1355,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat exp.
+	^ self asFloat exp.
     ].
     "/ very slow fallback
     ^ self exp_withAccuracy:self epsilon
@@ -1383,13 +1383,13 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asLongFloat ln.
+	^ self asLongFloat ln.
     ].
     "/ very slow fallback
     ^ self ln_withAccuracy:self epsilon
 
     "
-        (10 raisedTo:1000) ln
+	(10 raisedTo:1000) ln
     "
 !
 
@@ -1405,12 +1405,12 @@
 
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asLongFloat log10.
+	^ self asLongFloat log10.
     ].
     ^ self log:10
 
     "
-        (10 raisedTo:1000) log10
+	(10 raisedTo:1000) log10
     "
 !
 
@@ -1434,11 +1434,11 @@
     aNumber = 0 ifTrue:[^ 1].
     aNumber = 1 ifTrue:[^ self].
     aNumber isInteger ifTrue:[
-        ^ self raisedToInteger:aNumber
+	^ self raisedToInteger:aNumber
     ].
     aNumber isNumber ifFalse:[
-        ^ aNumber raisedFromNumber:self.
-    ].    
+	^ aNumber raisedFromNumber:self.
+    ].
     ^ self asFloat raisedTo:aNumber
 
     "
@@ -1448,8 +1448,8 @@
      -4 raisedTo: 1/2
      8 raisedTo: 1/3
      -8 raisedTo: 1/3
-     10 raisedTo: 4    
-     10 raisedTo: -4    
+     10 raisedTo: 4
+     10 raisedTo: -4
     "
 !
 
@@ -1468,7 +1468,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat sqrt.
+	^ self asFloat sqrt.
     ].
     "/ very slow fallback
     ^ self sqrt_withAccuracy:self epsilon
@@ -1488,7 +1488,7 @@
     ^ yN.
 
     "
-     (2 asFixedPoint:4) sqrtWithErrorLessThan:0.001   
+     (2 asFixedPoint:4) sqrtWithErrorLessThan:0.001
     "
 !
 
@@ -1497,7 +1497,7 @@
      For protocol completeness wrt. Squeak and ST80."
 
     anInteger >= 0 ifTrue:[
-        ^ self * (1 bitShift:anInteger)
+	^ self * (1 bitShift:anInteger)
     ].
     ^ self / (1 bitShift:anInteger negated)
 
@@ -1514,14 +1514,14 @@
 !Number methodsFor:'measurement values'!
 
 maxValue
-    "the maximum possible value taking me as a measurement with possible error; 
+    "the maximum possible value taking me as a measurement with possible error;
      as I am exact, thats myself"
 
     ^ self
 !
 
 minValue
-    "the minimum possible value taking me as a measurement with possible error; 
+    "the minimum possible value taking me as a measurement with possible error;
      as I am exact, thats myself"
 
     ^ self
@@ -1537,13 +1537,13 @@
     "/ what a kludge - Dolphin and Squeak mean: printOn: a stream;
     "/ ST/X (and some old ST80's) mean: 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.
     ].
 
     "
@@ -1590,9 +1590,9 @@
     |s|
 
     radix == 10 ifTrue:[
-        s := self printString.
+	s := self printString.
     ] ifFalse:[
-        s := self printStringRadix:radix.
+	s := self printStringRadix:radix.
     ].
     s printOn: aStream leftPaddedTo:size with: padCharacter
 
@@ -1611,24 +1611,24 @@
     |rest|
 
     self >= 1000 ifTrue:[
-        (self // 1000) printOn:aStream thousandsSeparator:thousandsSeparator.
-        thousandsSeparator printOn:aStream.
-        rest := self \\ 1000.
-        rest < 100 ifTrue:[
-            aStream nextPut:$0.
-            rest < 10 ifTrue:[
-                aStream nextPut:$0.
-            ].
-        ].
-        rest printOn:aStream.
-        ^ self.
+	(self // 1000) printOn:aStream thousandsSeparator:thousandsSeparator.
+	thousandsSeparator printOn:aStream.
+	rest := self \\ 1000.
+	rest < 100 ifTrue:[
+	    aStream nextPut:$0.
+	    rest < 10 ifTrue:[
+		aStream nextPut:$0.
+	    ].
+	].
+	rest printOn:aStream.
+	^ self.
     ].
     self printOn:aStream.
 
     "
      swiss style:
      1000000 printOn:Transcript thousandsSeparator:$'.     Transcript cr.
-     12345678 printOn:Transcript thousandsSeparator:$'.     Transcript cr.  
+     12345678 printOn:Transcript thousandsSeparator:$'.     Transcript cr.
      1234567 printOn:Transcript thousandsSeparator:$'.     Transcript cr.
      123456 printOn:Transcript thousandsSeparator:$'.     Transcript cr.
      123056 printOn:Transcript thousandsSeparator:$'.     Transcript cr.
@@ -1636,7 +1636,7 @@
      1234 printOn:Transcript thousandsSeparator:$'.     Transcript cr.
      123 printOn:Transcript thousandsSeparator:$'.     Transcript cr.
 
-     (12345678.12 asFixedPoint:2) printOn:Transcript thousandsSeparator:$'.     Transcript cr.  
+     (12345678.12 asFixedPoint:2) printOn:Transcript thousandsSeparator:$'.     Transcript cr.
      1234567.12 printOn:Transcript thousandsSeparator:$'.     Transcript cr.
      123456.12 printOn:Transcript thousandsSeparator:$'.     Transcript cr.
      123056.12 printOn:Transcript thousandsSeparator:$'.     Transcript cr.
@@ -1646,7 +1646,7 @@
 
      us style:
      1000000 printOn:Transcript thousandsSeparator:$,.     Transcript cr.
-     12345678 printOn:Transcript thousandsSeparator:$,.     Transcript cr.  
+     12345678 printOn:Transcript thousandsSeparator:$,.     Transcript cr.
      1234567 printOn:Transcript thousandsSeparator:$,.     Transcript cr.
      123456 printOn:Transcript thousandsSeparator:$,.     Transcript cr.
      12345 printOn:Transcript thousandsSeparator:$,.     Transcript cr.
@@ -1655,7 +1655,7 @@
 
      german (european ?) style
      1000000 printOn:Transcript thousandsSeparator:$..     Transcript cr.
-     12345678 printOn:Transcript thousandsSeparator:$..     Transcript cr.  
+     12345678 printOn:Transcript thousandsSeparator:$..     Transcript cr.
      1234567 printOn:Transcript thousandsSeparator:$..     Transcript cr.
      123456 printOn:Transcript thousandsSeparator:$..     Transcript cr.
      12345 printOn:Transcript thousandsSeparator:$..     Transcript cr.
@@ -1672,7 +1672,7 @@
     "return a string representation of the receiver in the specified
      base; does NOT prepend XXr to the string.
      See also: radixPrintStringRadix:
-               printOn:base:showRadix:"
+	       printOn:base:showRadix:"
 
     ^ self printStringRadix:base showRadix:false
 
@@ -1685,7 +1685,7 @@
     "return a string representation of the receiver in the specified
      base; does NOT prepend XXr to the string.
      See also: radixPrintStringRadix:
-               printOn:base:showRadix:"
+	       printOn:base:showRadix:"
 
     |s|
 
@@ -1719,21 +1719,21 @@
 
      1000000 asFixedPoint printStringWithThousandsSeparator
      12345678 asFixedPoint printStringWithThousandsSeparator
-     1234567 asFixedPoint printStringWithThousandsSeparator  
+     1234567 asFixedPoint printStringWithThousandsSeparator
      123456 asFixedPoint printStringWithThousandsSeparator
-     12345 asFixedPoint printStringWithThousandsSeparator 
-     1234 asFixedPoint printStringWithThousandsSeparator 
+     12345 asFixedPoint printStringWithThousandsSeparator
+     1234 asFixedPoint printStringWithThousandsSeparator
      123 asFixedPoint printStringWithThousandsSeparator
-     ((9999999//10000) asFixedPoint:9) printStringWithThousandsSeparator 
+     ((9999999//10000) asFixedPoint:9) printStringWithThousandsSeparator
     "
 !
 
 printStringWithThousandsSeparator:thousandsSeparator
     "print the receiver as business number with a thousands separator to aStream.
      Notice:
-        americans use comma
-        germans (europeans ?) use a dot
-        swiss people (business people ?) use a single quote
+	americans use comma
+	germans (europeans ?) use a dot
+	swiss people (business people ?) use a single quote
 
      Caveat: Should use the separator from the locale here"
 
@@ -1758,10 +1758,10 @@
 
      Transcript showCR:((1000000 asFixedPoint:2) printStringWithThousandsSeparator:$,).
      Transcript showCR:((12345678 asFixedPoint:2) printStringWithThousandsSeparator:$,).
-     Transcript showCR:((1234567 asFixedPoint:2) printStringWithThousandsSeparator:$,).  
+     Transcript showCR:((1234567 asFixedPoint:2) printStringWithThousandsSeparator:$,).
      Transcript showCR:((123456 asFixedPoint:2) printStringWithThousandsSeparator:$,).
-     Transcript showCR:((12345 asFixedPoint:2) printStringWithThousandsSeparator:$,). 
-     Transcript showCR:((1234 asFixedPoint:2) printStringWithThousandsSeparator:$,). 
+     Transcript showCR:((12345 asFixedPoint:2) printStringWithThousandsSeparator:$,).
+     Transcript showCR:((1234 asFixedPoint:2) printStringWithThousandsSeparator:$,).
      Transcript showCR:((123 asFixedPoint:2) printStringWithThousandsSeparator:$,).
     "
 !
@@ -1793,7 +1793,7 @@
 !
 
 storeString
-    "return a string for storing 
+    "return a string for storing
      - since numbers are literals, they store as they print."
 
     ^ self printString
@@ -1805,19 +1805,19 @@
     "compute the arcSine of the receiver using a taylor series approx."
 
     "/ uses taylor series:
-    "/                 1*x^3   1*3 * x^5   
+    "/                 1*x^3   1*3 * x^5
     "/    arcSin = x + ----- + ---------- + ...
-    "/                 2* 3    2*4 *  5    
+    "/                 2* 3    2*4 *  5
 
     |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 < -1) or:[self > 1]) ifTrue:[
+	^ self class
+	    raise:#domainErrorSignal
+	    receiver:self
+	    selector:#arcSin
+	    arguments:#()
+	    errorString:'bad receiver in arcSin'
     ].
 
     x2 := self * self.
@@ -1829,11 +1829,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
 
@@ -1848,7 +1848,7 @@
 
      0.5q arcSin_withAccuracy:1e-20     0.523598776
 
-     0.5 asLargeFloat arcSin_withAccuracy:1e-30    -- not yet 
+     0.5 asLargeFloat arcSin_withAccuracy:1e-30    -- not yet
 
 
      0.1 arcSin                                    0.100167
@@ -1861,7 +1861,7 @@
 
      0.1q arcSin_withAccuracy:1e-20     0.100167421
 
-     0.1 asLargeFloat arcSin_withAccuracy:1e-30    -- not yet 
+     0.1 asLargeFloat arcSin_withAccuracy:1e-30    -- not yet
     "
 !
 
@@ -1882,11 +1882,11 @@
     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
 
@@ -1899,8 +1899,8 @@
      1q arcTan_withAccuracy:0.01      0.790299653
      1q arcTan_withAccuracy:0.001     0.785897165
 
-     1q arcTan_withAccuracy:1e-8      0.785398168     
-     1q arcTan_withAccuracy:1e-20     -- not yet, converges very slow 
+     1q arcTan_withAccuracy:1e-8      0.785398168
+     1q arcTan_withAccuracy:1e-20     -- not yet, converges very slow
 
 
      0.5 arcTan                         0.463648
@@ -1912,36 +1912,36 @@
      0.5q arcTan_withAccuracy:0.001     0.463684276
 
      0.5q arcTan_withAccuracy:1e-20     0.463647609
-     0.5 asLargeFloat arcTan_withAccuracy:1e-30    -- not yet  
+     0.5 asLargeFloat arcTan_withAccuracy:1e-30    -- not yet
     "
 !
 
-cbrt_withAccuracy:epsilon 
+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
+		 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
 
@@ -1949,7 +1949,7 @@
      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.0000001          2.0
      8q cbrt_withAccuracy:0.0000000001       2.0
      8q cbrt_withAccuracy:0.000000000001     2.0
      8q cbrt_withAccuracy:LongFloat epsilon  2.0
@@ -1959,16 +1959,16 @@
      -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
+	]
      ]
     "
 !
@@ -1992,22 +1992,22 @@
     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_withAccuracy:1         0.5
-     1.0 asLongFloat cos_withAccuracy:0.1       0.541666667 
+     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.540302306
     "
 !
 
@@ -2029,28 +2029,28 @@
     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
 
     "
      1.0 cosh                                    1.54308
-     1.0q cosh_withAccuracy:1         1.5 
-     1.0q cosh_withAccuracy:0.1       1.54308 
-     1.0q cosh_withAccuracy:0.01      1.54308 
-     1.0q cosh_withAccuracy:0.001     1.54308 
-
-     1.0q cosh_withAccuracy:1e-40   -> 1.543080    
+     1.0q cosh_withAccuracy:1         1.5
+     1.0q cosh_withAccuracy:0.1       1.54308
+     1.0q cosh_withAccuracy:0.01      1.54308
+     1.0q cosh_withAccuracy:0.001     1.54308
+
+     1.0q cosh_withAccuracy:1e-40   -> 1.543080
     "
 !
 
 epsilon
-    "return the maximum relative spacing of instances of mySelf 
+    "return the maximum relative spacing of instances of mySelf
      (i.e. the value-delta of the least significant bit)"
 
     ^ self class epsilon
@@ -2074,12 +2074,12 @@
     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.
+	approx := approx + delta.
     ] doUntil:[delta abs <= epsilon].
 
     ^ approx
@@ -2088,7 +2088,7 @@
      -1 exp
      1.0 exp                                    2.71828
      1q exp                                     2.71828183
-     2q exp                                     7.3890561                        
+     2q exp                                     7.3890561
 
      1q exp_withAccuracy:1                      2.66666667
      1q exp_withAccuracy:0.1                    2.70833333
@@ -2097,9 +2097,9 @@
 
      2q exp_withAccuracy:LongFloat epsilon      7.3890561
 
-     1.0 asLongFloat exp_withAccuracy:1e-40     2.71828183 
-
-     5 exp_withAccuracy:1e-40      
+     1.0 asLongFloat exp_withAccuracy:1e-40     2.71828183
+
+     5 exp_withAccuracy:1e-40
      (1 exp_withAccuracy:1e-100) asFixedPoint:100
     "
 !
@@ -2108,32 +2108,32 @@
     "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
+	     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
+		   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
     "
 
     |denominator approx y y2 exp delta|
 
     self <= 0 ifTrue:[
-        ^ self class
-            raise:#domainErrorSignal
-            receiver:self
-            selector:#ln
-            arguments:#()
-            errorString:'bad receiver in ln'
+	^ self class
+	    raise:#domainErrorSignal
+	    receiver:self
+	    selector:#ln
+	    arguments:#()
+	    errorString:'bad receiver in ln'
     ].
-        
+
 
     y := (self - 1)/(self + 1).
     exp := y2 := y * y.
@@ -2142,10 +2142,10 @@
     denominator := 3.
 
     [
-        delta := exp / denominator.
-        approx := approx + delta.
-        exp := exp * y2.
-        denominator := denominator + 2.
+	delta := exp / denominator.
+	approx := approx + delta.
+	exp := exp * y2.
+	denominator := denominator + 2.
     ] doUntil:[delta <= epsilon].
 
     ^ y * 2 * approx.
@@ -2155,17 +2155,17 @@
      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: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                   
-     0 ln_withAccuracy:1e-40                   
+     2 ln_withAccuracy:1e-40
+     0 ln_withAccuracy:1e-40
 
      (2 ln_withAccuracy:1e-100) asFixedPoint:100
     "
@@ -2189,12 +2189,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
 
@@ -2203,7 +2203,7 @@
      1.0q sin                        0.841470985
 
      1.0q sin_withAccuracy:1         0.833333333
-     1.0q sin_withAccuracy:0.1       0.841666667 
+     1.0q sin_withAccuracy:0.1       0.841666667
      1.0q sin_withAccuracy:0.01      0.841666667
      1.0q sin_withAccuracy:0.001     0.841468254
 
@@ -2229,12 +2229,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
 
@@ -2243,47 +2243,47 @@
      1q sinh                        1.17520119
 
      1q sinh_withAccuracy:1         1.16666667
-     1q sinh_withAccuracy:0.1       1.175 
+     1q sinh_withAccuracy:0.1       1.175
      1q sinh_withAccuracy:0.01      1.175
      1q sinh_withAccuracy:0.001     1.17519841
 
-     1q sinh_withAccuracy:1e-40     1.17520119 
+     1q sinh_withAccuracy:1e-40     1.17520119
     "
 !
 
-sqrt_withAccuracy:epsilon 
+sqrt_withAccuracy:epsilon
     "compute square root of the receiver using newtom/heron algorithm"
     "
       Use the Heron algorithm:
 
-                 x_n + (a / x_n)
-        x_n+1 =  ---------------
-                      2
-
-        sqrt(a) = x_n
+		 x_n + (a / x_n)
+	x_n+1 =  ---------------
+		      2
+
+	sqrt(a) = x_n
     "
-    
+
     |approx|
 
     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.
     [
-        |lastApprox|
-
-        lastApprox := approx.
-        approx := ((self / approx) + approx) / 2.
-        (approx - lastApprox) abs > epsilon
+	|lastApprox|
+
+	lastApprox := approx.
+	approx := ((self / approx) + approx) / 2.
+	(approx - lastApprox) abs > epsilon
     ] whileTrue.
     ^ approx
 
@@ -2300,16 +2300,16 @@
      (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
+	]
      ]
     "
 !
@@ -2329,27 +2329,27 @@
     "/        num := (2 raisedTo:(2*n)) * ((2 raisedTo:(2*n))-1) * ((n*2) bernoulli).
     "/        den := (2*n) factorial.
     "/        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)).
+	(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.
 
@@ -2358,21 +2358,21 @@
     lastApprox := self.
     idx := 2.
     [
-        t := factors at:idx ifAbsent:[].
-        t isNil ifTrue:[
-            self error:'too many iterations'.
+	t := factors at:idx ifAbsent:[].
+	t isNil ifTrue:[
+	    self error:'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.
+	].
+	idx := idx + 1.
+	num := num * x2.
+
+	delta := num * t first / t second.
+	approx := approx + delta.
     ] doUntil:[delta abs <= epsilon].
     ^ approx
 
@@ -2396,19 +2396,19 @@
     "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
     "
 !
 
@@ -2421,11 +2421,11 @@
     ^ (self \\ aNumber) = 0
 
     "
-     3 isDivisibleBy:2     
+     3 isDivisibleBy:2
      4 isDivisibleBy:2
-     4.0 isDivisibleBy:2   
-     4.5 isDivisibleBy:4.5 
-     4.5 isDivisibleBy:1.0 
+     4.0 isDivisibleBy:2
+     4.5 isDivisibleBy:4.5
+     4.5 isDivisibleBy:1.0
     "
 !
 
@@ -2496,7 +2496,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat arcCos.
+	^ self asFloat arcCos.
     ].
     "/ slow fallback
     ^ (self class pi / 2) - self arcSin
@@ -2510,7 +2510,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat arcCosech.
+	^ self asFloat arcCosech.
     ].
     "/ slow fallback
     ^ ((1 + ((self*self)+1) sqrt) / self) ln
@@ -2524,7 +2524,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat arcCosh.
+	^ self asFloat arcCosh.
     ].
     "/ slow fallback
     ^ (self + (self*self-1) sqrt) ln.
@@ -2538,7 +2538,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat arcCoth.
+	^ self asFloat arcCoth.
     ].
     "/ slow fallback
     ^ ((self+1) / (self-1)) ln / 2
@@ -2552,7 +2552,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat arcSech.
+	^ self asFloat arcSech.
     ].
     "/ slow fallback
     ^ ((1 + (1-(self*self)) sqrt) / self) ln
@@ -2565,7 +2565,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat arcSin.
+	^ self asFloat arcSin.
     ].
     "/ very slow fallback
     ^ self arcSin_withAccuracy:self epsilon
@@ -2579,7 +2579,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat arcSinh.
+	^ self asFloat arcSinh.
     ].
     "/ slow fallback
     ^ ( self + (self*self+1) sqrt ) ln
@@ -2593,7 +2593,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat arcTan.
+	^ self asFloat arcTan.
     ].
     "/ very slow fallback
     ^ self arcTan_withAccuracy:self epsilon
@@ -2606,7 +2606,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat arcTan2:x.
+	^ self asFloat arcTan2:x.
     ].
     "/ very slow fallback
     ^ self arcTan2_withAccuracy:self epsilon x:x
@@ -2615,12 +2615,12 @@
 arcTanh
     "return the inverse hyperbolic tangent of the receiver."
     "caveat: misnomer; should be called aTanh or arTanh"
-    
+
     "/ 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 arcTanh.
+	^ self asFloat arcTanh.
     ].
     "/ slow fallback
     ^ ((1 + self) / (1 - self)) ln / 2
@@ -2634,7 +2634,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat cos.
+	^ self asFloat cos.
     ].
     "/ very slow fallback
     ^ self cos_withAccuracy:self epsilon
@@ -2647,7 +2647,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat cosh.
+	^ self asFloat cosh.
     ].
     "/ very slow fallback
     ^ self cosh_withAccuracy:self epsilon
@@ -2666,7 +2666,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat sin.
+	^ self asFloat sin.
     ].
     ^ self sin_withAccuracy:self epsilon
 !
@@ -2678,7 +2678,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat sinh.
+	^ self asFloat sinh.
     ].
     ^ self sinh_withAccuracy:self epsilon
 !
@@ -2697,7 +2697,7 @@
     "/ retry after converting to float
     (self isLimitedPrecisionReal not
     or:[self generality < 1.0 generality]) ifTrue:[
-        ^ self asFloat tanh.
+	^ self asFloat tanh.
     ].
     "/ very slow fallback
     ^ self tanh_withAccuracy:self epsilon
@@ -2715,7 +2715,7 @@
 "/    "/      (exp(x) - exp(-x)) / 2
 "/    "/      ----------------------
 "/    "/      (exp(x) + exp(-x)) / 2
-"/    
+"/
 "/    exp := self exp.
 "/    nexp := self negated exp.
 "/
@@ -2725,12 +2725,12 @@
 !Number methodsFor:'truncation & rounding'!
 
 detentBy: detent atMultiplesOf: grid snap: snap
-    "Map all values that are within detent/2 of any multiple of grid 
-     to that multiple.  
-     Otherwise, if snap is true, return self, meaning that the values 
-     in the dead zone will never be returned.  
+    "Map all values that are within detent/2 of any multiple of grid
+     to that multiple.
+     Otherwise, if snap is true, return self, meaning that the values
+     in the dead zone will never be returned.
      If snap is false, then expand the range between dead zones
-     so that it covers the range between multiples of the grid, 
+     so that it covers the range between multiples of the grid,
      and scale the value by that factor."
 
     | r1 r2 |
@@ -2740,16 +2740,16 @@
     snap ifTrue: [^ self].                       "...or return self"
 
     r2 := self < r1                               "Nearest end of dead zone"
-            ifTrue: [r1 - (detent asFloat/2)]
-            ifFalse: [r1 + (detent asFloat/2)].
+	    ifTrue: [r1 - (detent asFloat/2)]
+	    ifFalse: [r1 + (detent asFloat/2)].
 
     "Scale values between dead zones to fill range between multiples"
     ^ r1 + ((self - r2) * grid asFloat / (grid - detent))
 
     "
-     (170 to: 190 by: 2) collect: [:a | a detentBy: 10 atMultiplesOf: 90 snap: true]         
+     (170 to: 190 by: 2) collect: [:a | a detentBy: 10 atMultiplesOf: 90 snap: true]
      (170 to: 190 by: 2) collect: [:a | a detentBy: 10 atMultiplesOf: 90 snap: false]
-     (3.9 to: 4.1 by: 0.02) collect: [:a | a detentBy: 0.1 atMultiplesOf: 1.0 snap: true]    
+     (3.9 to: 4.1 by: 0.02) collect: [:a | a detentBy: 0.1 atMultiplesOf: 1.0 snap: true]
      (-3.9 to: -4.1 by: -0.02) collect: [:a | a detentBy: 0.1 atMultiplesOf: 1.0 snap: false]
     "
 !
@@ -2763,10 +2763,10 @@
 
     "
      1234.56789 fractionPart
-     1.2345e6 fractionPart  
-
-     1.6 asLongFloat fractionPart + 1.6 asLongFloat truncated    
-     -1.6 asLongFloat fractionPart + -1.6 asLongFloat truncated    
+     1.2345e6 fractionPart
+
+     1.6 asLongFloat fractionPart + 1.6 asLongFloat truncated
+     -1.6 asLongFloat fractionPart + -1.6 asLongFloat truncated
     "
 
     "Modified: / 4.11.1996 / 20:26:54 / cg"
@@ -2780,14 +2780,14 @@
     ^ self truncated asFloat
 
     "
-     1234.56789 integerPart 
-     1.2345e6 integerPart   
-     12.5 integerPart 
-     -12.5 integerPart 
-     (5/3) integerPart  
-     (-5/3) integerPart 
-     (5/3) truncated  
-     (-5/3) truncated  
+     1234.56789 integerPart
+     1.2345e6 integerPart
+     12.5 integerPart
+     -12.5 integerPart
+     (5/3) integerPart
+     (-5/3) integerPart
+     (5/3) truncated
+     (-5/3) truncated
     "
 
     "Created: / 28.10.1998 / 17:14:56 / cg"