Integer.st
changeset 19076 6765dbf123d8
parent 19071 2941ec17cf5d
child 19078 2196ad510fd1
--- a/Integer.st	Thu Jan 21 17:37:20 2016 +0100
+++ b/Integer.st	Thu Jan 21 19:09:01 2016 +0100
@@ -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
@@ -32,7 +32,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
@@ -49,18 +49,18 @@
     See details in concrete subclasses LargeInteger and SmallInteger.
 
     Mixed mode arithmetic:
-        int op int         -> int
-        int op fix         -> fix; scale is fix's scale
-        int op fraction    -> fraction
-        int op float       -> float
+	int op int         -> int
+	int op fix         -> fix; scale is fix's scale
+	int op fraction    -> fraction
+	int op float       -> float
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [see also:]
-        Number
-        LargeInteger SmallInteger
-        Float ShortFloat Fraction FixedPoint
+	Number
+	LargeInteger SmallInteger
+	Float ShortFloat Fraction FixedPoint
 "
 ! !
 
@@ -69,7 +69,7 @@
 byte1:b1 byte2:b2 byte3:b3 byte4:b4
     "Squeak compatibility:
      Return an Integer given four value bytes.
-     The returned integer is either a Small- or a LargeInteger 
+     The returned integer is either a Small- or a LargeInteger
      (on 32bit systems - on 64bit systems, it will be always a SmallInteger)"
 
     |t|
@@ -103,17 +103,17 @@
 
 %{   /* NOCONTEXT */
     if (__isStringLike(aString) && __isSmallInteger(startIndex)) {
-        char *cp = (char *)(__stringVal(aString));
-        int idx = __intVal(startIndex) - 1;
-        unsigned INT val;
-
-        if ((unsigned)idx < __stringSize(aString)) {
-            val = atoi(cp + idx);
-            if (val <= _MAX_INT) {
-                RETURN(__mkSmallInteger(val));
-            }
-            RETURN (__MKUINT(val));
-        }
+	char *cp = (char *)(__stringVal(aString));
+	int idx = __intVal(startIndex) - 1;
+	unsigned INT val;
+
+	if ((unsigned)idx < __stringSize(aString)) {
+	    val = atoi(cp + idx);
+	    if (val <= _MAX_INT) {
+		RETURN(__mkSmallInteger(val));
+	    }
+	    RETURN (__MKUINT(val));
+	}
     }
 %}.
     self primitiveFailed.
@@ -132,17 +132,17 @@
      Integer fastFromString:'12345' at:0
 
      Time millisecondsToRun:[
-        100000 timesRepeat:[
-            Integer readFrom:'12345'
-        ]
+	100000 timesRepeat:[
+	    Integer readFrom:'12345'
+	]
      ]
     "
 
     "
      Time millisecondsToRun:[
-        100000 timesRepeat:[
-            Integer fastFromString:'12345' at:1
-        ]
+	100000 timesRepeat:[
+	    Integer fastFromString:'12345' at:1
+	]
      ]
     "
 !
@@ -159,11 +159,11 @@
 
     val := 0.
     aByteArray do:[:twoDigits |
-        |hi lo|
-
-        hi := (twoDigits bitShift:-4) bitAnd:16r0F.
-        lo := twoDigits bitAnd:16r0F.
-        val := (val * 100) + (hi * 10) + lo
+	|hi lo|
+
+	hi := (twoDigits bitShift:-4) bitAnd:16r0F.
+	lo := twoDigits bitAnd:16r0F.
+	val := (val * 100) + (hi * 10) + lo
     ].
     ^ val
 
@@ -190,16 +190,16 @@
 
     val := 0.
     aByteArray do:[:twoDigits |
-        |hi lo|
-
-        lo := (twoDigits bitShift:-4) bitAnd:16r0F.
-        hi := twoDigits bitAnd:16r0F.
-        lo <= 9 ifTrue:[
-            val := (val * 100) + (hi * 10) + lo
-        ] ifFalse:[
-            "16rF is used to encode an odd number of digits"
-            val := (val * 10) + hi.
-        ].
+	|hi lo|
+
+	lo := (twoDigits bitShift:-4) bitAnd:16r0F.
+	hi := twoDigits bitAnd:16r0F.
+	lo <= 9 ifTrue:[
+	    val := (val * 100) + (hi * 10) + lo
+	] ifFalse:[
+	    "16rF is used to encode an odd number of digits"
+	    val := (val * 10) + hi.
+	].
     ].
     ^ val
 
@@ -222,9 +222,9 @@
      negative specifies if the result should be a negative number.
      The digits can be stored byte-wise into the result, using digitAt:put:"
 
-    ^ LargeInteger basicNew 
-            numberOfDigits:numberOfBytes
-            sign:(negative ifTrue:[-1] ifFalse:[1])
+    ^ LargeInteger basicNew
+	    numberOfDigits:numberOfBytes
+	    sign:(negative ifTrue:[-1] ifFalse:[1])
 !
 
 readFrom:aStringOrStream
@@ -255,41 +255,41 @@
     |value|
 
     Error handle:[:ex |
-        ^ exceptionBlock value
+	^ exceptionBlock value
     ] do:[
-        |str nextChar negative|
-
-        str := aStringOrStream readStream.
-
-        nextChar := str skipSeparators.
-        (nextChar == $-) ifTrue:[
-            negative := true.
-            str next.
-            nextChar := str peekOrNil
-        ] ifFalse:[
-            negative := false
-        ].
-        (nextChar isNil or:[nextChar isDigit not]) ifTrue:[
-            "
-             the string does not represent an integer
-            "
-            ^ exceptionBlock value
-        ].
-        value := self readFrom:str radix:10.
-        nextChar := str peekOrNil.
-        ((nextChar == $r) or:[ nextChar == $R]) ifTrue:[
-            "-xxr<number> is invalid; should be xxr-<val>"
-
-            negative ifTrue:[
-                'Integer [warning]: invalid (negative) radix ignored' errorPrintCR.
-                negative := false
-            ].
-            str next.
-            value := self readFrom:str radix:value
-        ].
-        negative ifTrue:[
-            value := value negated
-        ].
+	|str nextChar negative|
+
+	str := aStringOrStream readStream.
+
+	nextChar := str skipSeparators.
+	(nextChar == $-) ifTrue:[
+	    negative := true.
+	    str next.
+	    nextChar := str peekOrNil
+	] ifFalse:[
+	    negative := false
+	].
+	(nextChar isNil or:[nextChar isDigit not]) ifTrue:[
+	    "
+	     the string does not represent an integer
+	    "
+	    ^ exceptionBlock value
+	].
+	value := self readFrom:str radix:10.
+	nextChar := str peekOrNil.
+	((nextChar == $r) or:[ nextChar == $R]) ifTrue:[
+	    "-xxr<number> is invalid; should be xxr-<val>"
+
+	    negative ifTrue:[
+		'Integer [warning]: invalid (negative) radix ignored' errorPrintCR.
+		negative := false
+	    ].
+	    str next.
+	    value := self readFrom:str radix:value
+	].
+	negative ifTrue:[
+	    value := value negated
+	].
     ].
     ^ value
 
@@ -339,7 +339,7 @@
 
     nextChar := str peekOrNil.
     (nextChar notNil and:[nextChar isDigitRadix:radix]) ifFalse:[
-        ^ exceptionBlock value
+	^ exceptionBlock value
     ].
 
     value := nextChar digitValue.
@@ -365,29 +365,29 @@
     r4 := r2 * r2.
 
     [nextChar notNil and:[ (digit1 := nextChar digitValueRadix:r) notNil]] whileTrue:[
-        "/ read 4 chars and pre-compute their value to avoid largeInt operations.
-
-        str next.
-        nextChar2 := str peekOrNil.
-        (nextChar2 isNil or:[ (digit2 := nextChar2 digitValueRadix:r) isNil]) ifTrue:[
-            ^ (value * r) + digit1.
-        ].
-
-        str next.
-        nextChar3 := str peekOrNil.
-        (nextChar3 isNil or:[ (digit3 := nextChar3 digitValueRadix:r) isNil]) ifTrue:[
-            ^ (value * r2) + ((digit1*r) + digit2).
-        ].
-
-        str next.
-        nextChar4 := str peekOrNil.
-        (nextChar4 isNil or:[ (digit4 := nextChar4 digitValueRadix:r) isNil]) ifTrue:[
-            ^ (value * r3) + ((((digit1*r) + digit2)*r) + digit3).
-        ].
-
-        value := (value * r4) + ((((((digit1*r) + digit2)*r) + digit3)*r) + digit4).
-        str next.
-        nextChar := str peekOrNil.
+	"/ read 4 chars and pre-compute their value to avoid largeInt operations.
+
+	str next.
+	nextChar2 := str peekOrNil.
+	(nextChar2 isNil or:[ (digit2 := nextChar2 digitValueRadix:r) isNil]) ifTrue:[
+	    ^ (value * r) + digit1.
+	].
+
+	str next.
+	nextChar3 := str peekOrNil.
+	(nextChar3 isNil or:[ (digit3 := nextChar3 digitValueRadix:r) isNil]) ifTrue:[
+	    ^ (value * r2) + ((digit1*r) + digit2).
+	].
+
+	str next.
+	nextChar4 := str peekOrNil.
+	(nextChar4 isNil or:[ (digit4 := nextChar4 digitValueRadix:r) isNil]) ifTrue:[
+	    ^ (value * r3) + ((((digit1*r) + digit2)*r) + digit3).
+	].
+
+	value := (value * r4) + ((((((digit1*r) + digit2)*r) + digit3)*r) + digit4).
+	str next.
+	nextChar := str peekOrNil.
     ].
     ^ value
 
@@ -400,9 +400,9 @@
      Integer readFrom:'gg' radix:10 onError:0
 
      Time millisecondsToRun:[
-        1000 timesRepeat:[
-            (String new:1000 withAll:$1) asInteger
-        ]
+	1000 timesRepeat:[
+	    (String new:1000 withAll:$1) asInteger
+	]
      ]
     "
 
@@ -421,14 +421,14 @@
      stopOnSeparator finish|
 
     romanValues := Dictionary
-                    withKeys:'MDCLXVI' "/ #($M $D $C $L $X $V $I)
-                    andValues:#(1000 500 100 50 10 5 1).
+		    withKeys:'MDCLXVI' "/ #($M $D $C $L $X $V $I)
+		    andValues:#(1000 500 100 50 10 5 1).
 
     (stopOnSeparator := aStringOrStream isStream) ifFalse:[
-        s := aStringOrStream readStream.
+	s := aStringOrStream readStream.
     ].
     s atEnd ifTrue:[
-        ^ RomanNumberFormatError raiseErrorString:'empty string'
+	^ RomanNumberFormatError raiseErrorString:'empty string'
     ].
     val := 0.
     prevDigitVal := 99999.
@@ -436,61 +436,61 @@
     finish := false.
 
     [s atEnd or:[finish]] whileFalse:[
-        c := s next asUppercase.
-        c isSeparator ifTrue:[
-            stopOnSeparator ifFalse:[
-                ^ RomanNumberFormatError raiseErrorString:'garbage at the end'
-            ].
-            finish := true.
-        ] ifFalse:[
-            digitVal := romanValues at:c ifAbsent:nil.
-            digitVal isNil ifTrue:[
-                ^ RomanNumberFormatError raiseErrorString:'invalid character'
-            ].
-
-            digitVal = prevDigitVal ifTrue:[
-                ( #( 1 10 100 1000) includes:digitVal) ifFalse:[
-                    ^ RomanNumberFormatError raiseErrorString:'character may not be repeated'
-                ].
-                val := val + digitVal.
-                countSame := countSame + 1.
-                countSame >= 4 ifTrue:[
-                    digitVal ~= 1000 ifTrue:[
-                        countSame > 4 ifTrue:[
-                            "/ this is a bad roman number (such as MCCCCCCCCXXXXXXII);
-                            "/ Its not correct, but sometimes encountered on buildings.
-                            "/ If you do not want to be too picky,
-                            "/ provide a proceeding handler in order to proceed the conversion.
-                            BadRomanNumberFormatError raiseRequestErrorString:'more than 4 occurrences of same character'
-                        ] ifFalse:[
-                            "/ this is a naive roman number (such as VIIII);
-                            "/ Its not correct, but very often encountered (especially as page numbers).
-                            "/ The notification below normally goes unnoticed, unless some input validator
-                            "/ wants to be very picky, and treat this as an error.
-                            "/ To do so, provide a handler for NaiveRomanNumberFormatNotification.
-                            NaiveRomanNumberFormatNotification raiseRequestErrorString:'more than 3 occurrences of same character'.
-                        ]
-                    ]
-                ].
-            ] ifFalse:[
-                digitVal < prevDigitVal ifTrue:[
-                    val := val + digitVal.
-                ] ifFalse:[
-                    countSame == 1 ifFalse:[
-                        ^ RomanNumberFormatError raiseErrorString:'invalid character combination'
-                    ].
-                    delta := digitVal - prevDigitVal.
-                    ( #( 4 9 40 90 400 900) includes:delta) ifFalse:[
-                        ^ RomanNumberFormatError raiseErrorString:'invalid character combination'
-                    ].
-                    val := val - prevDigitVal.
-                    val := val + delta.
-                    digitVal := prevDigitVal - 0.1.  "/ trick: prevent prevDigit from arriving again.
-                ].
-                countSame := 1.
-            ].
-            prevDigitVal := digitVal.
-        ].
+	c := s next asUppercase.
+	c isSeparator ifTrue:[
+	    stopOnSeparator ifFalse:[
+		^ RomanNumberFormatError raiseErrorString:'garbage at the end'
+	    ].
+	    finish := true.
+	] ifFalse:[
+	    digitVal := romanValues at:c ifAbsent:nil.
+	    digitVal isNil ifTrue:[
+		^ RomanNumberFormatError raiseErrorString:'invalid character'
+	    ].
+
+	    digitVal = prevDigitVal ifTrue:[
+		( #( 1 10 100 1000) includes:digitVal) ifFalse:[
+		    ^ RomanNumberFormatError raiseErrorString:'character may not be repeated'
+		].
+		val := val + digitVal.
+		countSame := countSame + 1.
+		countSame >= 4 ifTrue:[
+		    digitVal ~= 1000 ifTrue:[
+			countSame > 4 ifTrue:[
+			    "/ this is a bad roman number (such as MCCCCCCCCXXXXXXII);
+			    "/ Its not correct, but sometimes encountered on buildings.
+			    "/ If you do not want to be too picky,
+			    "/ provide a proceeding handler in order to proceed the conversion.
+			    BadRomanNumberFormatError raiseRequestErrorString:'more than 4 occurrences of same character'
+			] ifFalse:[
+			    "/ this is a naive roman number (such as VIIII);
+			    "/ Its not correct, but very often encountered (especially as page numbers).
+			    "/ The notification below normally goes unnoticed, unless some input validator
+			    "/ wants to be very picky, and treat this as an error.
+			    "/ To do so, provide a handler for NaiveRomanNumberFormatNotification.
+			    NaiveRomanNumberFormatNotification raiseRequestErrorString:'more than 3 occurrences of same character'.
+			]
+		    ]
+		].
+	    ] ifFalse:[
+		digitVal < prevDigitVal ifTrue:[
+		    val := val + digitVal.
+		] ifFalse:[
+		    countSame == 1 ifFalse:[
+			^ RomanNumberFormatError raiseErrorString:'invalid character combination'
+		    ].
+		    delta := digitVal - prevDigitVal.
+		    ( #( 4 9 40 90 400 900) includes:delta) ifFalse:[
+			^ RomanNumberFormatError raiseErrorString:'invalid character combination'
+		    ].
+		    val := val - prevDigitVal.
+		    val := val + delta.
+		    digitVal := prevDigitVal - 0.1.  "/ trick: prevent prevDigit from arriving again.
+		].
+		countSame := 1.
+	    ].
+	    prevDigitVal := digitVal.
+	].
     ].
 "/    val > 5000 ifTrue:[
 "/        ^ RomanNumberFormatError raiseErrorStirng:'number out of range (1..5000)'
@@ -518,86 +518,86 @@
      Integer readFromRomanString:'MCCCCCCCCXXXXXXIIIIII'
 
      BadRomanNumberFormatError ignoreIn:[
-         Integer readFromRomanString:'MCCCCCCCCXXXXXXIIIIII'
+	 Integer readFromRomanString:'MCCCCCCCCXXXXXXIIIIII'
      ]
     "
 
 
     "naive cases:
      #(
-        'MCMXCIX'           1999
-        'MCMXCVIIII'        1999
-        'MCMLXXXXIX'        1999
-        'MDCCCCXCIX'        1999
-        'MDCCCCXCVIIII'     1999
-        'MDCCCCLXXXXIX'     1999
-        'MDCCCCLXXXXVIIII'  1999
+	'MCMXCIX'           1999
+	'MCMXCVIIII'        1999
+	'MCMLXXXXIX'        1999
+	'MDCCCCXCIX'        1999
+	'MDCCCCXCVIIII'     1999
+	'MDCCCCLXXXXIX'     1999
+	'MDCCCCLXXXXVIIII'  1999
      ) pairWiseDo:[:goodString :expectedValue |
-        (Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
+	(Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
      ]
     "
 
 
     "error cases:
       #(
-        'XIIX'
-        'VV'
-        'VVV'
-        'XXL'
-        'XLX'
-        'LC'
-        'LL'
-        'DD'
+	'XIIX'
+	'VV'
+	'VVV'
+	'XXL'
+	'XLX'
+	'LC'
+	'LL'
+	'DD'
      ) do:[:badString |
-        (Integer readFromRomanString:badString onError:nil) notNil ifTrue:[self halt].
+	(Integer readFromRomanString:badString onError:nil) notNil ifTrue:[self halt].
      ]
     "
 
     "good cases:
      #( 'I'     1
-        'II'    2
-        'III'   3
-        'IV'    4
-        'V'     5
-        'VI'    6
-        'VII'   7
-        'VIII'  8
-        'IX'    9
-        'X'     10
-        'XI'    11
-        'XII'   12
-        'XIII'  13
-        'XIV'   14
-        'XV'    15
-        'XVI'   16
-        'XVII'  17
-        'XVIII' 18
-        'XIX'   19
-        'XX'    20
-        'XXX'   30
-        'L'     50
-        'XL'    40
-        'LX'    60
-        'LXX'   70
-        'LXXX'  80
-        'CXL'   140
-        'CL'    150
-        'CLX'   160
-        'MMM'                   3000
-        'MMMM'                  4000
-        'MMMMCMXCIX'            4999
-        'MMMMMMMMMCMXCIX'       9999
+	'II'    2
+	'III'   3
+	'IV'    4
+	'V'     5
+	'VI'    6
+	'VII'   7
+	'VIII'  8
+	'IX'    9
+	'X'     10
+	'XI'    11
+	'XII'   12
+	'XIII'  13
+	'XIV'   14
+	'XV'    15
+	'XVI'   16
+	'XVII'  17
+	'XVIII' 18
+	'XIX'   19
+	'XX'    20
+	'XXX'   30
+	'L'     50
+	'XL'    40
+	'LX'    60
+	'LXX'   70
+	'LXXX'  80
+	'CXL'   140
+	'CL'    150
+	'CLX'   160
+	'MMM'                   3000
+	'MMMM'                  4000
+	'MMMMCMXCIX'            4999
+	'MMMMMMMMMCMXCIX'       9999
      ) pairWiseDo:[:goodString :expectedValue |
-        (Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
+	(Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
      ]
     "
 
     "
       1 to:9999 do:[:n |
-        |romanString|
-
-        romanString := String streamContents:[:stream | n printRomanOn:stream].
-        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
+	|romanString|
+
+	romanString := String streamContents:[:stream | n printRomanOn:stream].
+	(Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
      ]
     "
 !
@@ -612,12 +612,12 @@
     |val|
 
     RomanNumberFormatError
-        handle:[:ex |
-            val := exceptionalValue value
-        ]
-        do:[
-            val := self readFromRomanString:aStringOrStream
-        ].
+	handle:[:ex |
+	    val := exceptionalValue value
+	]
+	do:[
+	    val := self readFromRomanString:aStringOrStream
+	].
     ^ val
 
 
@@ -640,85 +640,85 @@
 
     "error cases:
       #(
-        'XIIX'
-        'VV'
-        'VVV'
-        'XXL'
-        'XLX'
-        'LC'
-        'LL'
-        'DD'
+	'XIIX'
+	'VV'
+	'VVV'
+	'XXL'
+	'XLX'
+	'LC'
+	'LL'
+	'DD'
      ) do:[:badString |
-        (Integer readFromRomanString:badString onError:nil) notNil ifTrue:[self halt].
+	(Integer readFromRomanString:badString onError:nil) notNil ifTrue:[self halt].
      ]
     "
 
     "naive (but handled) cases:
       #(
-        'IIII'   4
-        'VIIII'  9
-        'XIIII'  14
-        'XVIIII' 19
+	'IIII'   4
+	'VIIII'  9
+	'XIIII'  14
+	'XVIIII' 19
      ) pairWiseDo:[:goodString :expectedValue |
-        (Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
+	(Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
      ]
     "
 
     "good cases:
      #( 'I'     1
-        'II'    2
-        'III'   3
-        'IV'    4
-        'V'     5
-        'VI'    6
-        'VII'   7
-        'VIII'  8
-        'IX'    9
-        'X'     10
-        'XI'    11
-        'XII'   12
-        'XIII'  13
-        'XIV'   14
-        'XV'    15
-        'XVI'   16
-        'XVII'  17
-        'XVIII' 18
-        'XIX'   19
-        'XX'    20
-        'XXX'   30
-        'L'     50
-        'XL'    40
-        'LX'    60
-        'LXX'   70
-        'LXXX'  80
-        'CXL'   140
-        'CL'    150
-        'CLX'   160
-        'MMM'                   3000
-        'MMMM'                  4000
-        'MMMMCMXCIX'            4999
-        'MMMMMMMMMCMXCIX'       9999
+	'II'    2
+	'III'   3
+	'IV'    4
+	'V'     5
+	'VI'    6
+	'VII'   7
+	'VIII'  8
+	'IX'    9
+	'X'     10
+	'XI'    11
+	'XII'   12
+	'XIII'  13
+	'XIV'   14
+	'XV'    15
+	'XVI'   16
+	'XVII'  17
+	'XVIII' 18
+	'XIX'   19
+	'XX'    20
+	'XXX'   30
+	'L'     50
+	'XL'    40
+	'LX'    60
+	'LXX'   70
+	'LXXX'  80
+	'CXL'   140
+	'CL'    150
+	'CLX'   160
+	'MMM'                   3000
+	'MMMM'                  4000
+	'MMMMCMXCIX'            4999
+	'MMMMMMMMMCMXCIX'       9999
      ) pairWiseDo:[:goodString :expectedValue |
-        (Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
+	(Integer readFromRomanString:goodString onError:nil) ~= expectedValue ifTrue:[self halt].
      ]
     "
 
     "
       1 to:9999 do:[:n |
-        |romanString|
-
-        romanString := String streamContents:[:stream | n printRomanOn:stream].
-        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
+	|romanString|
+
+	romanString := String streamContents:[:stream | n printRomanOn:stream].
+	(Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
      ]
     "
 
     "reading naive numbers:
 
       1 to:9999 do:[:n |
-        |romanString|
-
-        romanString := String streamContents:[:stream | n printRomanOn:stream naive:true].
-        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
+	|romanString|
+
+	romanString := String streamContents:[:stream | n printRomanOn:stream naive:true].
+	(Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
      ]
     "
 !
@@ -757,9 +757,9 @@
 
 initialize
     BCDConversionErrorSignal isNil ifTrue:[
-        BCDConversionErrorSignal := ConversionError newSignal.
-        BCDConversionErrorSignal nameClass:self message:#bcdConversionErrorSignal.
-        BCDConversionErrorSignal notifierString:'bcd conversion error'.
+	BCDConversionErrorSignal := ConversionError newSignal.
+	BCDConversionErrorSignal nameClass:self message:#bcdConversionErrorSignal.
+	BCDConversionErrorSignal notifierString:'bcd conversion error'.
     ].
 
     "Modified: / 15.11.1999 / 20:36:04 / cg"
@@ -823,7 +823,7 @@
     PrimeCache := nil.
     bits := BooleanArray new:limit//2.
     self primesUpTo:limit do:[:p |
-        bits at:p//2 put:true
+	bits at:p//2 put:true
     ].
     PrimeCache := bits.
 
@@ -838,11 +838,11 @@
     "
      Integer flushPrimeCache.
      Transcript showCR:(
-        Time millisecondsToRun:[ 1 to:100000 do:[:n | n isPrime] ]
+	Time millisecondsToRun:[ 1 to:100000 do:[:n | n isPrime] ]
      ).
      Integer initializePrimeCacheUpTo:100000.
      Transcript showCR:(
-        Time millisecondsToRun:[ 1 to:100000 do:[:n | n isPrime] ]
+	Time millisecondsToRun:[ 1 to:100000 do:[:n | n isPrime] ]
      ).
      Integer flushPrimeCache.
     "
@@ -879,45 +879,45 @@
 
     index := 6.
     2 to: 2309 do:[:n|
-        [(primesUpTo2310 at: index) < n]
-            whileTrue:[index := index + 1].
-        n = (primesUpTo2310 at: index) ifTrue:[
-            maskBitIndex at: n+1 put: (bitIndex := bitIndex + 1).
-        ] ifFalse:[
-            "if modulo any of the prime factors of 2310, then could not be prime"
-            (n \\ 2 = 0 or:[n \\ 3 = 0 or:[n \\ 5 = 0 or:[n \\ 7 = 0 or:[n \\ 11 = 0]]]])
-                    ifTrue:[maskBitIndex at: n+1 put: 0]
-                    ifFalse:[maskBitIndex at: n+1 put: (bitIndex := bitIndex + 1)].
-        ].
+	[(primesUpTo2310 at: index) < n]
+	    whileTrue:[index := index + 1].
+	n = (primesUpTo2310 at: index) ifTrue:[
+	    maskBitIndex at: n+1 put: (bitIndex := bitIndex + 1).
+	] ifFalse:[
+	    "if modulo any of the prime factors of 2310, then could not be prime"
+	    (n \\ 2 = 0 or:[n \\ 3 = 0 or:[n \\ 5 = 0 or:[n \\ 7 = 0 or:[n \\ 11 = 0]]]])
+		    ifTrue:[maskBitIndex at: n+1 put: 0]
+		    ifFalse:[maskBitIndex at: n+1 put: (bitIndex := bitIndex + 1)].
+	].
     ].
 
     "Now the real work begins...
     Start with 13 since multiples of 2,3,5,7,11 are handled by the storage method;
     increment by 2 for odd numbers only."
     13 to: limit by: 2 do:[:n|
-        (maskBit := maskBitIndex at: (n \\ 2310 + 1)) = 0 ifFalse:["not a multiple of 2,3,5,7,11"
-            byteIndex := n // 2310 * 60 + (maskBit-1 bitShift: -3) + 1.
-            bitIndex := 1 bitShift: (maskBit bitAnd: 7).
-            ((flags at: byteIndex) bitAnd: bitIndex) = 0 ifFalse:["not marked -- n is prime"
-                aBlock value: n.
-                "Start with n*n since any integer < n has already been sieved
-                (e.g., any multiple of n with a number k < n has been cleared
-                when k was sieved); add 2 * i to avoid even numbers and
-                mark all multiples of this prime. Note: n < indexLimit below
-                limits running into LargeInts -- nothing more."
-                n < indexLimit ifTrue:[
-                    index := n * n.
-                    (index bitAnd: 1) = 0 ifTrue:[index := index + n].
-                    [index <= limit] whileTrue:[
-                        (maskBit := maskBitIndex at: (index \\ 2310 + 1)) = 0 ifFalse:[
-                            byteIndex := (index // 2310 * 60) + (maskBit-1 bitShift: -3) + 1.
-                            maskBit := 255 - (1 bitShift: (maskBit bitAnd: 7)).
-                            flags at: byteIndex put: ((flags at: byteIndex) bitAnd: maskBit).
-                        ].
-                        index := index + (2 * n)].
-                ].
-            ].
-        ].
+	(maskBit := maskBitIndex at: (n \\ 2310 + 1)) = 0 ifFalse:["not a multiple of 2,3,5,7,11"
+	    byteIndex := n // 2310 * 60 + (maskBit-1 bitShift: -3) + 1.
+	    bitIndex := 1 bitShift: (maskBit bitAnd: 7).
+	    ((flags at: byteIndex) bitAnd: bitIndex) = 0 ifFalse:["not marked -- n is prime"
+		aBlock value: n.
+		"Start with n*n since any integer < n has already been sieved
+		(e.g., any multiple of n with a number k < n has been cleared
+		when k was sieved); add 2 * i to avoid even numbers and
+		mark all multiples of this prime. Note: n < indexLimit below
+		limits running into LargeInts -- nothing more."
+		n < indexLimit ifTrue:[
+		    index := n * n.
+		    (index bitAnd: 1) = 0 ifTrue:[index := index + n].
+		    [index <= limit] whileTrue:[
+			(maskBit := maskBitIndex at: (index \\ 2310 + 1)) = 0 ifFalse:[
+			    byteIndex := (index // 2310 * 60) + (maskBit-1 bitShift: -3) + 1.
+			    maskBit := 255 - (1 bitShift: (maskBit bitAnd: 7)).
+			    flags at: byteIndex put: ((flags at: byteIndex) bitAnd: maskBit).
+			].
+			index := index + (2 * n)].
+		].
+	    ].
+	].
     ].
 
     "
@@ -928,7 +928,7 @@
 
 primeCacheSize
     "see comment in initializePrimeCacheUpTo:limit"
-    
+
     ^ PrimeCache size * 2
 
     "
@@ -941,11 +941,11 @@
     "
      Integer flushPrimeCache.
      Transcript showCR:(
-        Time millisecondsToRun:[ 1 to:100000 do:[:n | n isPrime] ]
+	Time millisecondsToRun:[ 1 to:100000 do:[:n | n isPrime] ]
      ).
      Integer initializePrimeCacheUpTo:100000.
      Transcript showCR:(
-        Time millisecondsToRun:[ 1 to:100000 do:[:n | n isPrime] ]
+	Time millisecondsToRun:[ 1 to:100000 do:[:n | n isPrime] ]
      ).
      Integer flushPrimeCache.
     "
@@ -955,26 +955,26 @@
     "/ primes up to 1000
 
     ^ #(
-            2 3   5   7  11  13  17  19  23  29  31  37  41  43  47  53  59  61  67  71
-             73  79  83  89  97 101 103 107 109 113 127 131 137 139 149 151 157 163 167
-            173 179 181 191 193 197 199 211 223 227 229 233 239 241 251 257 263 269 271
-            277 281 283 293 307 311 313 317 331 337 347 349 353 359 367 373 379 383 389
-            397 401 409 419 421 431 433 439 443 449 457 461 463 467 479 487 491 499 503
-            509 521 523 541 547 557 563 569 571 577 587 593 599 601 607 613 617 619 631
-            641 643 647 653 659 661 673 677 683 691 701 709 719 727 733 739 743 751 757
-            761 769 773 787 797 809 811 821 823 827 829 839 853 857 859 863 877 881 883
-            887 907 911 919 929 937 941 947 953 967 971 977 983 991 997
-
-            1009 1013 1019 1021 1031 1033 1039 1049 1051 1061 1063 1069 1087 1091 1093
-            1097 1103 1109 1117 1123 1129 1151 1153 1163 1171 1181 1187 1193 1201 1213
-            1217 1223 1229 1231 1237 1249 1259 1277 1279 1283 1289 1291 1297 1301 1303
-            1307 1319 1321 1327 1361 1367 1373 1381 1399 1409 1423 1427 1429 1433 1439
-            1447 1451 1453 1459 1471 1481 1483 1487 1489 1493 1499 1511 1523 1531 1543
-            1549 1553 1559 1567 1571 1579 1583 1597 1601 1607 1609 1613 1619 1621 1627
-            1637 1657 1663 1667 1669 1693 1697 1699 1709 1721 1723 1733 1741 1747 1753
-            1759 1777 1783 1787 1789 1801 1811 1823 1831 1847 1861 1867 1871 1873 1877
-            1879 1889 1901 1907 1913 1931 1933 1949 1951 1973 1979 1987 1993 1997 1999
-        ).
+	    2 3   5   7  11  13  17  19  23  29  31  37  41  43  47  53  59  61  67  71
+	     73  79  83  89  97 101 103 107 109 113 127 131 137 139 149 151 157 163 167
+	    173 179 181 191 193 197 199 211 223 227 229 233 239 241 251 257 263 269 271
+	    277 281 283 293 307 311 313 317 331 337 347 349 353 359 367 373 379 383 389
+	    397 401 409 419 421 431 433 439 443 449 457 461 463 467 479 487 491 499 503
+	    509 521 523 541 547 557 563 569 571 577 587 593 599 601 607 613 617 619 631
+	    641 643 647 653 659 661 673 677 683 691 701 709 719 727 733 739 743 751 757
+	    761 769 773 787 797 809 811 821 823 827 829 839 853 857 859 863 877 881 883
+	    887 907 911 919 929 937 941 947 953 967 971 977 983 991 997
+
+	    1009 1013 1019 1021 1031 1033 1039 1049 1051 1061 1063 1069 1087 1091 1093
+	    1097 1103 1109 1117 1123 1129 1151 1153 1163 1171 1181 1187 1193 1201 1213
+	    1217 1223 1229 1231 1237 1249 1259 1277 1279 1283 1289 1291 1297 1301 1303
+	    1307 1319 1321 1327 1361 1367 1373 1381 1399 1409 1423 1427 1429 1433 1439
+	    1447 1451 1453 1459 1471 1481 1483 1487 1489 1493 1499 1511 1523 1531 1543
+	    1549 1553 1559 1567 1571 1579 1583 1597 1601 1607 1609 1613 1619 1621 1627
+	    1637 1657 1663 1667 1669 1693 1697 1699 1709 1721 1723 1733 1741 1747 1753
+	    1759 1777 1783 1787 1789 1801 1811 1823 1831 1847 1861 1867 1871 1873 1877
+	    1879 1889 1901 1907 1913 1931 1933 1949 1951 1973 1979 1987 1993 1997 1999
+	).
 !
 
 primesUpTo: max
@@ -994,8 +994,8 @@
      N := 1000.
      p := 1.
      a := (1 to:1000)
-         collect:[:i | p := p nextPrime. p ]
-         thenSelect:[:p | p <= N].
+	 collect:[:i | p := p nextPrime. p ]
+	 thenSelect:[:p | p <= N].
      b := Integer primesUpTo:N.
      self assert:(a = b)
     "
@@ -1005,8 +1005,8 @@
      N := 1000 nextPrime.
      p := 1.
      a := (1 to:1000)
-         collect:[:i | p := p nextPrime. p ]
-         thenSelect:[:p | p <= N].
+	 collect:[:i | p := p nextPrime. p ]
+	 thenSelect:[:p | p <= N].
      b := Integer primesUpTo:N.
      self assert:(a = b)
     "
@@ -1016,8 +1016,8 @@
      N := 1000 nextPrime-1.
      p := 1.
      a := (1 to:1000)
-         collect:[:i | p := p nextPrime. p ]
-         thenSelect:[:p | p <= N].
+	 collect:[:i | p := p nextPrime. p ]
+	 thenSelect:[:p | p <= N].
      b := Integer primesUpTo:N.
      self assert:(a = b)
     "
@@ -1027,8 +1027,8 @@
      N := 100000.
      p := 1.
      a := (1 to:N)
-         collect:[:i | p := p nextPrime. p ]
-         thenSelect:[:p | p <= N].
+	 collect:[:i | p := p nextPrime. p ]
+	 thenSelect:[:p | p <= N].
      b := Integer primesUpTo:N.
      self assert:(a = b)
     "
@@ -1038,8 +1038,8 @@
      N := 100000 nextPrime.
      p := 1.
      a := (1 to:N)
-         collect:[:i | p := p nextPrime. p ]
-         thenSelect:[:p | p <= N].
+	 collect:[:i | p := p nextPrime. p ]
+	 thenSelect:[:p | p <= N].
      b := Integer primesUpTo:N.
      self assert:(a = b)
     "
@@ -1049,8 +1049,8 @@
      N := 100000 nextPrime-1.
      p := 1.
      a := (1 to:N)
-         collect:[:i | p := p nextPrime. p ]
-         thenSelect:[:p | p <= N].
+	 collect:[:i | p := p nextPrime. p ]
+	 thenSelect:[:p | p <= N].
      b := Integer primesUpTo:N.
      self assert:(a = b)
     "
@@ -1059,25 +1059,25 @@
 primesUpTo: max do: aBlock
     "Compute aBlock with all prime integers up to and including the given integer.
      See comment in initializePrimeCacheUpTo:limit"
-     
+
     | limit flags prime k |
 
     max <= 2000 ifTrue:[
-        self primesUpTo2000 do:[:p |
-            p > max ifTrue:[^ self].
-            aBlock value:p.
-        ].
-        ^ self.
+	self primesUpTo2000 do:[:p |
+	    p > max ifTrue:[^ self].
+	    aBlock value:p.
+	].
+	^ self.
     ].
 
     max <= self primeCacheSize ifTrue:[
-        aBlock value:2.
-        3 to:max by:2 do:[:p |
-            (PrimeCache at:p//2) ifTrue:[
-                aBlock value:p
-            ].
-        ].
-        ^ self.
+	aBlock value:2.
+	3 to:max by:2 do:[:p |
+	    (PrimeCache at:p//2) ifTrue:[
+		aBlock value:p
+	    ].
+	].
+	^ self.
     ].
 
     limit := max asInteger - 1.
@@ -1088,15 +1088,15 @@
     "/ sieve, on the fly
     flags := (ByteArray new: limit) atAllPut: 1.
     1 to: limit do: [:i |
-        (flags at: i) == 1 ifTrue: [
-            prime := i + 1.
-            k := i + prime.
-            [k <= limit] whileTrue: [
-                flags at: k put: 0.
-                k := k + prime
-            ].
-            aBlock value: prime
-        ]
+	(flags at: i) == 1 ifTrue: [
+	    prime := i + 1.
+	    k := i + prime.
+	    [k <= limit] whileTrue: [
+		flags at: k put: 0.
+		k := k + prime
+	    ].
+	    aBlock value: prime
+	]
     ].
 
     "
@@ -1137,10 +1137,10 @@
 & aNumber
     "return the bitwise-and of the receiver and the argument, anInteger.
      Same as bitAnd: - added for compatibility with Dolphin Smalltalk.
-     Notice: 
-        please do not use ^ for integers in new code; it makes the code harder
-        to understand, as it may be not obvious, whether a boolean or a bitWise or is intended.
-        For integers, use bitAnd: to make the intention explicit."
+     Notice:
+	please do not use ^ for integers in new code; it makes the code harder
+	to understand, as it may be not obvious, whether a boolean or a bitWise or is intended.
+	For integers, use bitAnd: to make the intention explicit."
 
     ^ self bitAnd:aNumber
 
@@ -1176,20 +1176,20 @@
     "Answer the result of setting/resetting the specified mask in the receiver."
 
     ^ aBoolean
-            ifTrue:  [self bitOr:integerMask]
-            ifFalse: [self bitClear:integerMask]
+	    ifTrue:  [self bitOr:integerMask]
+	    ifFalse: [self bitClear:integerMask]
 
     "turn on the 1-bit:
-         |v|
-
-         v := 2r0100.
-         v mask:1 set:true
+	 |v|
+
+	 v := 2r0100.
+	 v mask:1 set:true
 
      turn off the 1-bit:
-         |v|
-
-         v := 2r0101.
-         v mask:1 set:false
+	 |v|
+
+	 v := 2r0101.
+	 v mask:1 set:false
     "
 !
 
@@ -1231,10 +1231,10 @@
 | aNumber
     "return the bitwise-or of the receiver and the argument, anInteger.
      Same as bitOr: - added for compatibility with Dolphin Smalltalk.
-     Notice: 
-        please do not use | for integers in new code; it makes the code harder
-        to understand, as it may be not obvious, whether a boolean or a bitWise or is intended.
-        For integers, use bitOr: to make the intention explicit."
+     Notice:
+	please do not use | for integers in new code; it makes the code harder
+	to understand, as it may be not obvious, whether a boolean or a bitWise or is intended.
+	For integers, use bitOr: to make the intention explicit."
 
     ^ self bitOr:aNumber
 
@@ -1249,8 +1249,8 @@
 asByteArray
     "return my hexBytes in MSB.
      Do not use:
-        This is a very stupid squeak-compatibility method,
-        as normally, you'd expect the bytes to be ordered in the machine's natve order"
+	This is a very stupid squeak-compatibility method,
+	as normally, you'd expect the bytes to be ordered in the machine's natve order"
 
     ^ self digitBytesMSB
 !
@@ -1259,10 +1259,10 @@
     "return my hexBytes in MSB, optionally padded at the left with zeros"
 
     "(((
-        | repeats number | 
-        repeats := 1000000.
-        number := 123456789123456789123456789123456789123456789123456789.
-         [repeats timesRepeat: (number asByteArrayOfSize: 1024) ] timeToRun.
+	| repeats number |
+	repeats := 1000000.
+	number := 123456789123456789123456789123456789123456789123456789.
+	 [repeats timesRepeat: (number asByteArrayOfSize: 1024) ] timeToRun.
      )))"
 
     | bytes bytesSize|
@@ -1270,10 +1270,10 @@
     bytes := self digitBytesMSB.
     bytesSize := bytes size.
     size < bytesSize ifTrue: [
-        ^ ConversionError raiseRequestWith:self errorString:'number too big for ', size asString
+	^ ConversionError raiseRequestWith:self errorString:'number too big for ', size asString
     ].
     ^ (ByteArray new:size)
-            replaceFrom:size-bytesSize+1 to:size with:bytes startingAt:1.
+	    replaceFrom:size-bytesSize+1 to:size with:bytes startingAt:1.
 
     "
      123 asByteArrayOfSize:1 #[123]
@@ -1282,7 +1282,7 @@
 
      255 asByteArrayOfSize:1 #[255]
 
-     256 asByteArrayOfSize:1 
+     256 asByteArrayOfSize:1
      256 asByteArrayOfSize:2
      256 asByteArrayOfSize:4
     "
@@ -1317,9 +1317,9 @@
     ^ (self printStringRadix:base) leftPaddedTo:size with:padChar
 
     "
-     1234 printPaddedWith:$0 to:4 base:16     
-     1234 printLeftPaddedWith:$0 to:4 base:16 
-     128 printLeftPaddedWith:$0 to:2 base:16  
+     1234 printPaddedWith:$0 to:4 base:16
+     1234 printLeftPaddedWith:$0 to:4 base:16
+     128 printLeftPaddedWith:$0 to:2 base:16
     "
 !
 
@@ -1361,7 +1361,7 @@
 
     "funny - although the romans did not have negative numbers - squeak has"
     self negative ifTrue:[
-        ^ '-' , self negated romanPrintString
+	^ '-' , self negated romanPrintString
     ].
     ^ self romanPrintString
 !
@@ -1406,15 +1406,15 @@
     rslt := 0.
     multiplier := 1.
     [v > 0] whileTrue:[
-        nibble := v bitAnd:16r0F.
-        nibble > 9 ifTrue:[
-            ^ BCDConversionErrorSignal
-                    raiseRequestWith:self
-                    errorString:'bad BCD coded value'
-        ].
-        rslt := rslt + (nibble * multiplier).
-        multiplier := multiplier * 10.
-        v := v bitShift:-4.
+	nibble := v bitAnd:16r0F.
+	nibble > 9 ifTrue:[
+	    ^ BCDConversionErrorSignal
+		    raiseRequestWith:self
+		    errorString:'bad BCD coded value'
+	].
+	rslt := rslt + (nibble * multiplier).
+	multiplier := multiplier * 10.
+	v := v bitShift:-4.
     ].
     ^ rslt
 
@@ -1449,9 +1449,9 @@
     v := self.
     rslt := shift := 0.
     [v > 0] whileTrue:[
-        rslt := rslt + ((v \\ 10) bitShift:shift).
-        shift := shift + 4.
-        v := v // 10.
+	rslt := rslt + ((v \\ 10) bitShift:shift).
+	shift := shift + 4.
+	v := v // 10.
     ].
     ^ rslt
 
@@ -1504,18 +1504,18 @@
      result byte|
 
     aMaskInteger isInteger ifFalse:[
-        ^ aMaskInteger bitAndFromInteger:self.
+	^ aMaskInteger bitAndFromInteger:self.
     ].
 
     n := (aMaskInteger digitLength) min:(self digitLength).
     result := self class basicNew numberOfDigits:n.
 
     1 to:n do:[:index |
-        byte := (aMaskInteger digitAt:index) bitAnd:(self digitAt:index).
-        result digitAt:index put:byte.
+	byte := (aMaskInteger digitAt:index) bitAnd:(self digitAt:index).
+	result digitAt:index put:byte.
     ].
     (byte == 0 or:[n <= SmallInteger maxBytes]) ifTrue:[
-        ^ result compressed
+	^ result compressed
     ].
     ^ result
 
@@ -1543,11 +1543,11 @@
     result := self class basicNew numberOfDigits:n.
 
     1 to:n do:[:index |
-        byte :=  (self digitAt:index) bitClear:(aMaskInteger digitAt:index).
-        result digitAt:index put:byte.
+	byte :=  (self digitAt:index) bitClear:(aMaskInteger digitAt:index).
+	result digitAt:index put:byte.
     ].
     (byte == 0 or:[n <= SmallInteger maxBytes]) ifTrue:[
-        ^ result compressed
+	^ result compressed
     ].
     ^ result
 !
@@ -1562,8 +1562,8 @@
     cnt := 0.
 
     1 to:n do:[:index |
-        byte := self digitAt:index.
-        cnt := cnt + (byte bitCount)
+	byte := self digitAt:index.
+	cnt := cnt + (byte bitCount)
     ].
     ^ cnt
 
@@ -1593,13 +1593,13 @@
     result := self class basicNew numberOfDigits:n.
 
     1 to:n do:[:index |
-        byte := self digitAt:index.
-        byte := byte bitInvert bitAnd:16rFF.
-        result digitAt:index put:byte.
+	byte := self digitAt:index.
+	byte := byte bitInvert bitAnd:16rFF.
+	result digitAt:index put:byte.
     ].
     (byte == 0 or:[n <= SmallInteger maxBytes]) ifTrue:[
-        "if last byte is zero we can normalize"
-        ^ result compressed
+	"if last byte is zero we can normalize"
+	^ result compressed
     ].
     ^ result
 
@@ -1632,15 +1632,15 @@
      result byte|
 
     aMaskInteger isInteger ifFalse:[
-        ^ aMaskInteger bitOrFromInteger:self.
+	^ aMaskInteger bitOrFromInteger:self.
     ].
 
     n := (aMaskInteger digitLength) max:(self digitLength).
     result := self class basicNew numberOfDigits:n.
 
     1 to:n do:[:index |
-        byte := (aMaskInteger digitAt:index) bitOr:(self digitAt:index).
-        result digitAt:index put:byte.
+	byte := (aMaskInteger digitAt:index) bitOr:(self digitAt:index).
+	result digitAt:index put:byte.
     ].
 "/ no need to normalize - if the operands were correct
 "/    byte == 0 ifTrue:[
@@ -1654,9 +1654,9 @@
      leftShift if shiftCount > 0; rightShift otherwise.
 
      Notice: the result of bitShift: on negative receivers is not
-             defined in the language standard (since the implementation
-             is free to choose any internal representation for integers)
-             However, ST/X preserves the sign."
+	     defined in the language standard (since the implementation
+	     is free to choose any internal representation for integers)
+	     However, ST/X preserves the sign."
 
     |result
      prev       "{ Class: SmallInteger }"
@@ -1671,143 +1671,143 @@
      nDigits    "{ Class: SmallInteger }" |
 
     shiftCount isInteger ifFalse:[
-        ^ shiftCount bitShiftFromInteger:self.
+	^ shiftCount bitShiftFromInteger:self.
     ].
 
     shiftCount > 0 ifTrue:[
-        "left shift"
-
-        digitShift := shiftCount // 8.
-        bitShift := shiftCount \\ 8.
-        n := self digitLength.
-
-        "
-         modulo 8 shifts can be done faster ...
-        "
-        bitShift == 0 ifTrue:[
-            n := n + digitShift.
-            result := self class basicNew numberOfDigits:n sign:self sign.
-            result digitBytes replaceFrom:(digitShift + 1) to:n with:self digitBytes.
-            "
-             no normalize needed, since receiver was already normalized
-            "
-            ^ result
-        ].
-
-        "
-         less-than-8 shifts can be done faster ...
-        "
-        digitShift == 0 ifTrue:[
-            nn := n+1.
-            result := self class basicNew numberOfDigits:nn sign:self sign.
-            prev := 0.
-            1 to:n do:[:index |
-                byte := self digitAt:index.
-                byte := (byte bitShift:bitShift) bitOr:prev.
-                result digitAt:index put:(byte bitAnd:16rFF).
-                prev := byte bitShift:-8.
-            ].
-            result digitAt:nn put:prev.
-            "
-             might have stored a 0-byte ...
-            "
-            prev == 0 ifTrue:[
-                ^ result compressed
-            ].
-            ^ result.
-        ].
-
-        "
-         slow case ...
-        "
-        n := n + digitShift + 1.
-        result := self class basicNew numberOfDigits:n sign:self sign.
-        byte := self digitAt:1.
-        byte := (byte bitShift:bitShift) bitAnd:16rFF.
-        result digitAt:(digitShift + 1) put:byte.
-        revShift := -8 + bitShift.
-        nDigits := self digitLength.
-        2 to:nDigits do:[:index |
-            byte := self digitAt:index.
-            byte2 := self digitAt:index-1.
-            byte := byte bitShift:bitShift.
-            byte2 := byte2 bitShift:revShift.
-            byte := (byte bitOr:byte2) bitAnd:16rFF.
-            result digitAt:(index + digitShift) put:byte.
-        ].
-        byte2 := self digitAt:nDigits.
-        byte2 := (byte2 bitShift:revShift) bitAnd:16rFF.
-        result digitAt:(nDigits + digitShift + 1) put:byte2.
-        "
-         might have stored a 0-byte ...
-        "
-        byte2 == 0 ifTrue:[
-            ^ result compressed
-        ].
-        ^ result
+	"left shift"
+
+	digitShift := shiftCount // 8.
+	bitShift := shiftCount \\ 8.
+	n := self digitLength.
+
+	"
+	 modulo 8 shifts can be done faster ...
+	"
+	bitShift == 0 ifTrue:[
+	    n := n + digitShift.
+	    result := self class basicNew numberOfDigits:n sign:self sign.
+	    result digitBytes replaceFrom:(digitShift + 1) to:n with:self digitBytes.
+	    "
+	     no normalize needed, since receiver was already normalized
+	    "
+	    ^ result
+	].
+
+	"
+	 less-than-8 shifts can be done faster ...
+	"
+	digitShift == 0 ifTrue:[
+	    nn := n+1.
+	    result := self class basicNew numberOfDigits:nn sign:self sign.
+	    prev := 0.
+	    1 to:n do:[:index |
+		byte := self digitAt:index.
+		byte := (byte bitShift:bitShift) bitOr:prev.
+		result digitAt:index put:(byte bitAnd:16rFF).
+		prev := byte bitShift:-8.
+	    ].
+	    result digitAt:nn put:prev.
+	    "
+	     might have stored a 0-byte ...
+	    "
+	    prev == 0 ifTrue:[
+		^ result compressed
+	    ].
+	    ^ result.
+	].
+
+	"
+	 slow case ...
+	"
+	n := n + digitShift + 1.
+	result := self class basicNew numberOfDigits:n sign:self sign.
+	byte := self digitAt:1.
+	byte := (byte bitShift:bitShift) bitAnd:16rFF.
+	result digitAt:(digitShift + 1) put:byte.
+	revShift := -8 + bitShift.
+	nDigits := self digitLength.
+	2 to:nDigits do:[:index |
+	    byte := self digitAt:index.
+	    byte2 := self digitAt:index-1.
+	    byte := byte bitShift:bitShift.
+	    byte2 := byte2 bitShift:revShift.
+	    byte := (byte bitOr:byte2) bitAnd:16rFF.
+	    result digitAt:(index + digitShift) put:byte.
+	].
+	byte2 := self digitAt:nDigits.
+	byte2 := (byte2 bitShift:revShift) bitAnd:16rFF.
+	result digitAt:(nDigits + digitShift + 1) put:byte2.
+	"
+	 might have stored a 0-byte ...
+	"
+	byte2 == 0 ifTrue:[
+	    ^ result compressed
+	].
+	^ result
     ].
 
     shiftCount < 0 ifTrue:[
-        "right shift"
-
-        digitShift := shiftCount negated // 8.
-        bitShift := shiftCount negated \\ 8.
-        n := self digitLength.
-
-        digitShift >= n ifTrue:[
-            ^ 0
-        ].
-
-        "
-         modulo 8 shifts can be done faster ...
-        "
-        bitShift == 0 ifTrue:[
-            n := n-digitShift.
-            result := self class basicNew numberOfDigits:n sign:self sign.
-            result digitBytes replaceFrom:1 to:n with:self digitBytes startingAt:(digitShift + 1) .
-            n <= SmallInteger maxBytes ifTrue:[
-                ^ result compressed
-            ].
-            ^ result
-        ].
-
-        "
-         less-than-8 shifts can be done faster ...
-        "
-        digitShift == 0 ifTrue:[
-            result := self class basicNew numberOfDigits:n sign:self sign.
-            prev := 0.
-            bitShift := bitShift negated.
-            revShift := 8 + bitShift.
-            n to:1 by:-1 do:[:index |
-                byte := self digitAt:index.
-                next := (byte bitShift:revShift) bitAnd:16rFF.
-                byte := (byte bitShift:bitShift) bitOr:prev.
-                result digitAt:index put:(byte bitAnd:16rFF).
-                prev := next.
-            ].
-            ^ result compressed
-        ].
-
-        "
-         slow case ...
-        "
-        nn := n-digitShift.
-        result := self class basicNew numberOfDigits:nn sign:self sign.
-
-        prev := 0.
-        bitShift := bitShift negated.
-        revShift := 8 + bitShift.
-        nn := digitShift + 1.
-        n to:nn by:-1 do:[:index |
-            byte := self digitAt:index.
-            next := (byte bitShift:revShift) bitAnd:16rFF.
-            byte := (byte bitShift:bitShift) bitOr:prev.
-            result digitAt:(index - digitShift) put:byte.
-            prev := next.
-        ].
-        "the last stored byte ..."
-        ^ result compressed
+	"right shift"
+
+	digitShift := shiftCount negated // 8.
+	bitShift := shiftCount negated \\ 8.
+	n := self digitLength.
+
+	digitShift >= n ifTrue:[
+	    ^ 0
+	].
+
+	"
+	 modulo 8 shifts can be done faster ...
+	"
+	bitShift == 0 ifTrue:[
+	    n := n-digitShift.
+	    result := self class basicNew numberOfDigits:n sign:self sign.
+	    result digitBytes replaceFrom:1 to:n with:self digitBytes startingAt:(digitShift + 1) .
+	    n <= SmallInteger maxBytes ifTrue:[
+		^ result compressed
+	    ].
+	    ^ result
+	].
+
+	"
+	 less-than-8 shifts can be done faster ...
+	"
+	digitShift == 0 ifTrue:[
+	    result := self class basicNew numberOfDigits:n sign:self sign.
+	    prev := 0.
+	    bitShift := bitShift negated.
+	    revShift := 8 + bitShift.
+	    n to:1 by:-1 do:[:index |
+		byte := self digitAt:index.
+		next := (byte bitShift:revShift) bitAnd:16rFF.
+		byte := (byte bitShift:bitShift) bitOr:prev.
+		result digitAt:index put:(byte bitAnd:16rFF).
+		prev := next.
+	    ].
+	    ^ result compressed
+	].
+
+	"
+	 slow case ...
+	"
+	nn := n-digitShift.
+	result := self class basicNew numberOfDigits:nn sign:self sign.
+
+	prev := 0.
+	bitShift := bitShift negated.
+	revShift := 8 + bitShift.
+	nn := digitShift + 1.
+	n to:nn by:-1 do:[:index |
+	    byte := self digitAt:index.
+	    next := (byte bitShift:revShift) bitAnd:16rFF.
+	    byte := (byte bitShift:bitShift) bitOr:prev.
+	    result digitAt:(index - digitShift) put:byte.
+	    prev := next.
+	].
+	"the last stored byte ..."
+	^ result compressed
     ].
 
     ^ self "no shift"
@@ -1829,8 +1829,8 @@
     n := (aMaskInteger digitLength) min:(self digitLength).
 
     1 to:n do:[:index |
-        byte := (aMaskInteger digitAt:index) bitAnd:(self digitAt:index).
-        byte ~~ 0 ifTrue:[^ true].
+	byte := (aMaskInteger digitAt:index) bitAnd:(self digitAt:index).
+	byte ~~ 0 ifTrue:[^ true].
     ].
     ^ false
 
@@ -1858,18 +1858,18 @@
      result byte|
 
     anInteger isInteger ifFalse:[
-        ^ anInteger bitXorFromInteger:self.
+	^ anInteger bitXorFromInteger:self.
     ].
 
     n := (anInteger digitLength) max:(self digitLength).
     result := self class basicNew numberOfDigits:n.
 
     1 to:n do:[:index |
-        byte := (anInteger digitAt:index) bitXor:(self digitAt:index).
-        result digitAt:index put:byte.
+	byte := (anInteger digitAt:index) bitXor:(self digitAt:index).
+	result digitAt:index put:byte.
     ].
     (byte == 0 or:[n <= SmallInteger maxBytes]) ifTrue:[
-        ^ result compressed
+	^ result compressed
     ].
     ^ result
 
@@ -1890,12 +1890,12 @@
      but a new number is returned. Should be named #withMask:changedTo:"
 
     (aBooleanOrNumber == 0 or:[aBooleanOrNumber == false]) ifTrue:[
-        ^ self bitClear:mask
+	^ self bitClear:mask
     ].
     ^ self bitOr:mask
 
     "
-     (16r3fffffff changeMask:16r80 to:0) hexPrintString 
+     (16r3fffffff changeMask:16r80 to:0) hexPrintString
      (16r3fff0000 changeMask:16r80 to:1) hexPrintString
     "
 !
@@ -1924,7 +1924,7 @@
 
     byteNr := self digitLength.
     byteNr == 0 ifTrue:[
-        ^ 0
+	^ 0
     ].
     highByte := self digitAt:byteNr.
     ^ (byteNr - 1) * 8 + highByte highBit
@@ -1951,9 +1951,9 @@
      leftShift if shiftCount > 0; rightShift otherwise.
 
      Notice: the result of bitShift: on negative receivers is not
-             defined in the language standard (since the implementation
-             is free to choose any internal representation for integers)
-             However, ST/X preserves the sign."
+	     defined in the language standard (since the implementation
+	     is free to choose any internal representation for integers)
+	     However, ST/X preserves the sign."
 
     ^ self bitShift:shiftCount
 
@@ -1973,10 +1973,10 @@
 
     maxBytes := self digitLength.
     1 to:maxBytes do:[:byteIndex |
-        byte := self digitAt:byteIndex.
-        byte ~~ 0 ifTrue:[
-            ^ (byteIndex-1)*8 + (byte lowBit)
-        ].
+	byte := self digitAt:byteIndex.
+	byte ~~ 0 ifTrue:[
+	    ^ (byteIndex-1)*8 + (byte lowBit)
+	].
     ].
     ^ 0 "/ should not happen
 
@@ -2035,9 +2035,9 @@
      rightShift if shiftCount > 0; leftShift otherwise.
 
      Notice: the result of bitShift: on negative receivers is not
-             defined in the language standard (since the implementation
-             is free to choose any internal representation for integers)
-             However, ST/X preserves the sign."
+	     defined in the language standard (since the implementation
+	     is free to choose any internal representation for integers)
+	     However, ST/X preserves the sign."
 
     ^ self bitShift:(shiftCount negated)
 
@@ -2061,16 +2061,16 @@
 bitAt:index
     "return the value of the index's bit (index starts at 1) as 0 or 1.
      Notice: the result of bitAt: on negative receivers is not
-             defined in the language standard (since the implementation
-             is free to choose any internal representation for integers)"
+	     defined in the language standard (since the implementation
+	     is free to choose any internal representation for integers)"
 
     |i "{Class: SmallInteger}"|
 
     i := index - 1.
     i < 0 ifTrue:[
-        ^ SubscriptOutOfBoundsError
-                raiseRequestWith:index
-                errorString:'index out of bounds'
+	^ SubscriptOutOfBoundsError
+		raiseRequestWith:index
+		errorString:'index out of bounds'
     ].
     ^ (self digitAt:(i // 8 + 1)) bitAt:(i \\ 8 + 1)
 
@@ -2105,16 +2105,16 @@
      The index for the least significant bit is 1."
 
     1 to:self digitLength do:[:i8 |
-        |byte|
-
-        byte := self digitAt:i8.
-        byte ~~ 0 ifTrue:[
-            1 to:8 do:[:i |
-                (byte bitAt:i) == 1 ifTrue:[
-                    aBlock value:(((i8-1)*8) + i).
-                ].
-            ].
-        ]
+	|byte|
+
+	byte := self digitAt:i8.
+	byte ~~ 0 ifTrue:[
+	    1 to:8 do:[:i |
+		(byte bitAt:i) == 1 ifTrue:[
+		    aBlock value:(((i8-1)*8) + i).
+		].
+	    ].
+	]
     ].
 
     "
@@ -2132,16 +2132,16 @@
      The index for the least significant bit is 1."
 
     self digitLength downTo:1 do:[:i8 |
-        |byte|
-
-        byte := self digitAt:i8.
-        byte ~~ 0 ifTrue:[
-            8 downTo:1 do:[:i |
-                (byte bitAt:i) == 1 ifTrue:[
-                    aBlock value:(((i8-1)*8) + i).
-                ].
-            ].
-        ]
+	|byte|
+
+	byte := self digitAt:i8.
+	byte ~~ 0 ifTrue:[
+	    8 downTo:1 do:[:i |
+		(byte bitAt:i) == 1 ifTrue:[
+		    aBlock value:(((i8-1)*8) + i).
+		].
+	    ].
+	]
     ].
 
     "
@@ -2161,7 +2161,7 @@
      but a new number is returned. Should be named #withBit:changedTo:"
 
     (aBooleanOrNumber == 0 or:[aBooleanOrNumber == false]) ifTrue:[
-        ^ self clearBit:index
+	^ self clearBit:index
     ].
     ^ self setBit:index
 
@@ -2183,14 +2183,14 @@
      result byte|
 
     index <= 0 ifTrue:[
-        ^ SubscriptOutOfBoundsSignal
-                raiseRequestWith:index
-                errorString:'bit index out of bounds'
+	^ SubscriptOutOfBoundsSignal
+		raiseRequestWith:index
+		errorString:'bit index out of bounds'
     ].
     byteIndex := ((index - 1) // 8) + 1.
     n := self digitLength.
     byteIndex > n ifTrue:[
-        ^ self
+	^ self
     ].
 
     result := self simpleDeepCopy.
@@ -2198,7 +2198,7 @@
     byte := (result digitAt:byteIndex) clearBit:bitIndex.
     result digitAt:byteIndex put:byte.
     (byte == 0 or:[n == byteIndex and:[n <= SmallInteger maxBytes]]) ifTrue:[
-        ^ result compressed
+	^ result compressed
     ].
     ^ result
 
@@ -2216,9 +2216,9 @@
      but a new number is returned. Should be named #withBitInverted:"
 
     index <= 0 ifTrue:[
-        ^ SubscriptOutOfBoundsSignal
-                raiseRequestWith:index
-                errorString:'index out of bounds'
+	^ SubscriptOutOfBoundsSignal
+		raiseRequestWith:index
+		errorString:'index out of bounds'
     ].
     ^ self bitXor:(1 bitShift:index-1)
 
@@ -2268,9 +2268,9 @@
      but a new number is returned. Should be named #withBitSet:"
 
     index <= 0 ifTrue:[
-        ^ SubscriptOutOfBoundsSignal
-                raiseRequestWith:index
-                errorString:'index out of bounds'
+	^ SubscriptOutOfBoundsSignal
+		raiseRequestWith:index
+		errorString:'index out of bounds'
     ].
     ^ self bitOr:(1 bitShift:index-1)
 
@@ -2289,11 +2289,11 @@
     ^ self digitAt:anIndex
 
     "
-        12345678 byteAt:2
-        12345678 digitBytes at:2
-
-        -12345678 byteAt:2
-        -12345678 digitBytes at:2
+	12345678 byteAt:2
+	12345678 digitBytes at:2
+
+	-12345678 byteAt:2
+	-12345678 digitBytes at:2
     "
 !
 
@@ -2308,7 +2308,7 @@
 
     absLen := self negated digitLength.
     (self digitByteAt:absLen) == 16rFF ifTrue:[
-        ^ (absLen - 1) max:1
+	^ (absLen - 1) max:1
     ].
     ^ absLen
 
@@ -2343,7 +2343,7 @@
      otherwise least significant byte is first"
 
     msbFlag ifTrue:[
-        ^ self digitBytesMSB.
+	^ self digitBytesMSB.
     ].
     ^ self digitBytes
 
@@ -2364,23 +2364,23 @@
     |digitBytes|
 
     self negative ifTrue:[
-        RangeError raiseWith:self errorString:'negative numbers are not supported in #swapBytes'.
+	RangeError raiseWith:self errorString:'negative numbers are not supported in #swapBytes'.
     ].
     digitBytes := self digitBytes.
     digitBytes size odd ifTrue:[
-        "ByteArray<<#swapBytes needs even number of bytes.
-         Add 0 to the most significant position (the end)"
-        digitBytes := digitBytes copyWith:0.
-        
+	"ByteArray<<#swapBytes needs even number of bytes.
+	 Add 0 to the most significant position (the end)"
+	digitBytes := digitBytes copyWith:0.
+
     ].
     ^ (LargeInteger digitBytes:digitBytes swapBytes) compressed
 
     "
-        16rFFEE2211 swapBytes hexPrintString
-        16rFFEEAA2211 swapBytes hexPrintString
-        16r2211 swapBytes hexPrintString
-        16rFF3FFFFF swapBytes
-        self assert:(SmallInteger maxVal swapBytes swapBytes == SmallInteger maxVal)
+	16rFFEE2211 swapBytes hexPrintString
+	16rFFEEAA2211 swapBytes hexPrintString
+	16r2211 swapBytes hexPrintString
+	16rFF3FFFFF swapBytes
+	self assert:(SmallInteger maxVal swapBytes swapBytes == SmallInteger maxVal)
     "
 ! !
 
@@ -2390,7 +2390,7 @@
     "return the receiver as a fixedPoint number"
 
     ^ FixedPoint basicNew
-        setNumerator:self denominator:1 scale:1
+	setNumerator:self denominator:1 scale:1
 
     "
      100 asFixedPoint
@@ -2405,7 +2405,7 @@
      of post-decimal-point digits."
 
     ^ FixedPoint basicNew
-        setNumerator:self denominator:1 scale:scale
+	setNumerator:self denominator:1 scale:scale
 
     "
      100 asFixedPoint:2
@@ -2501,7 +2501,7 @@
      16r7FFFFF signExtended24BitValue
      16rFFFFFF signExtended24BitValue
     "
-    
+
     "Modified: / 07-05-1996 / 09:31:57 / cg"
     "Created: / 05-03-2012 / 14:37:55 / cg"
 !
@@ -2530,11 +2530,11 @@
      This may be useful for communication interfaces"
 
     |masked|
-    
+
     masked := self bitAnd:((1 bitShift:bitNr)-1).
     (self isBitSet:bitNr) ifTrue:[
-        ^ masked - (1 bitShift:bitNr)
-    ].    
+	^ masked - (1 bitShift:bitNr)
+    ].
     ^ masked
 
     "
@@ -2553,8 +2553,8 @@
      This may be useful for communication interfaces"
 
     (self bitTest:16r8000000000000000) ifTrue:[
-        ^ (self bitAnd:16rFFFFFFFFFFFFFFFF) - 16r10000000000000000
-    ].    
+	^ (self bitAnd:16rFFFFFFFFFFFFFFFF)-16r10000000000000000
+    ].
     ^ (self bitAnd:16r7FFFFFFFFFFFFFFF)
 
     "
@@ -2571,8 +2571,8 @@
      This may be useful for communication interfaces"
 
     (self bitTest:16r80000000) ifTrue:[
-        ^ (self bitAnd:16rFFFFFFFF) - 16r100000000
-    ].    
+	^ (self bitAnd:16rFFFFFFFF) - 16r100000000
+    ].
     ^ (self bitAnd:16r7FFFFFFF)
 
     "
@@ -2611,8 +2611,8 @@
     ^ self bitAnd:16r3FFFFFFF.
 
     "
-        -20000000000000 hash
-         20000000000000 hash
+	-20000000000000 hash
+	 20000000000000 hash
     "
 
     "Created: / 14.11.1996 / 12:12:27 / cg"
@@ -2638,8 +2638,8 @@
 
     d := aFraction denominator.
     ^ aFraction class
-        numerator:(aFraction numerator - (self * d))
-        denominator:d
+	numerator:(aFraction numerator - (self * d))
+	denominator:d
 
     "Modified: 28.7.1997 / 19:08:30 / cg"
 !
@@ -2667,7 +2667,7 @@
     denominator := aFraction denominator.
     numerator := aFraction numerator.
     (denominator == 1) ifFalse:[
-        ^ numerator = (self * denominator)
+	^ numerator = (self * denominator)
     ].
     ^ numerator = self
 !
@@ -2676,8 +2676,8 @@
     "sent when a fraction does not know how to multiply the receiver, an integer"
 
     ^ aFraction class
-        numerator:(self * aFraction numerator)
-        denominator:aFraction denominator
+	numerator:(self * aFraction numerator)
+	denominator:aFraction denominator
 
     "Modified: 28.7.1997 / 19:08:27 / cg"
 !
@@ -2687,8 +2687,8 @@
      Sent when aFraction does not know how to divide by the receiver."
 
     ^ aFraction class
-        numerator:aFraction numerator
-        denominator:(self * aFraction denominator)
+	numerator:aFraction numerator
+	denominator:(self * aFraction denominator)
 
     "Modified: 28.7.1997 / 19:08:23 / cg"
 !
@@ -2700,8 +2700,8 @@
 
     d := aFraction denominator.
     ^ aFraction class
-        numerator:(aFraction numerator + (self * d))
-        denominator:d
+	numerator:(aFraction numerator + (self * d))
+	denominator:d
 
     "Modified: 28.7.1997 / 19:08:11 / cg"
 !
@@ -2735,12 +2735,12 @@
     shift := selfLowBit min:argLowBit.
     b := b bitShift:(argLowBit negated).
     [a = 0] whileFalse:[
-        a := a bitShift:(selfLowBit negated).
-        a < b ifTrue:[
-            t := a. a := b. b := t
-        ].
-        a := a - b.
-        selfLowBit := a lowBit - 1.
+	a := a bitShift:(selfLowBit negated).
+	a < b ifTrue:[
+	    t := a. a := b. b := t
+	].
+	a := a - b.
+	selfLowBit := a lowBit - 1.
     ].
     ^ b bitShift:shift
 
@@ -2759,13 +2759,13 @@
     n := stop - self + 1.
     a := Array new:n.
     self to:stop do:[:i |
-        a at:(i-self+1) put:(aBlock value:i).
+	a at:(i-self+1) put:(aBlock value:i).
     ].
     ^ a.
 
     "
      1 to:10 collect:[:i | i squared]
-     10 to:20 collect:[:i | i squared]  
+     10 to:20 collect:[:i | i squared]
      (10 to:20) collect:[:i | i squared]
     "
 ! !
@@ -2807,7 +2807,7 @@
      Sometimes also called C(n,k) (for choose k from n)
 
      binCo is defined as:
-        n!!
+	n!!
      ----------
      k!! (n-k)!!
 
@@ -2828,13 +2828,13 @@
 
     kRun := k.
     kRun > (self / 2) ifTrue:[
-        "/ symmetry
-        kRun := self - kRun.
+	"/ symmetry
+	kRun := self - kRun.
     ].
 
     acc := 1.
     1 to:kRun do:[:i |
-        acc := acc * (self - kRun + i) / i.
+	acc := acc * (self - kRun + i) / i.
     ].
     ^ acc
 
@@ -2856,30 +2856,30 @@
 !
 
 divMod:aNumber
-    "return an array filled with 
-        (self // aNumber) and (self \\ aNumber).
+    "return an array filled with
+	(self // aNumber) and (self \\ aNumber).
      The returned remainder has the same sign as aNumber.
      The following is always true:
-        (receiver // something) * something + (receiver \\ something) = receiver
+	(receiver // something) * something + (receiver \\ something) = receiver
 
      Be careful with negative results: 9 // 4 -> 2, while -9 // 4 -> -3.
-     Especially surprising:     
-        -1 \\ 10 -> 9  (because -(1/10) is truncated towards next smaller integer, which is -1,
-                        and -1 multiplied by 10 gives -10, so we have to add 9 to get the original -1).
-        -10 \\ 3 -> 2 (because -(10/3) is truncated towards next smaller integer, which is -4,
-                        and -4 * 4 gives -12, so we need to add 2 to get the original -10.
+     Especially surprising:
+	-1 \\ 10 -> 9  (because -(1/10) is truncated towards next smaller integer, which is -1,
+			and -1 multiplied by 10 gives -10, so we have to add 9 to get the original -1).
+	-10 \\ 3 -> 2 (because -(10/3) is truncated towards next smaller integer, which is -4,
+			and -4 * 4 gives -12, so we need to add 2 to get the original -10.
 
      This may be redefined in some integer classes for
      more performance (where the remainder is generated as a side effect of division)"
 
     ^ Array
-        with:(self // aNumber)
-        with:(self \\ aNumber)
+	with:(self // aNumber)
+	with:(self \\ aNumber)
 
     "
      10 divMod:3       -> #(3 1)   because 3*3 + 1 = 10
      10 divMod:-3      -> #(-4 -2) because -4*-3 + (-2) = 10
-     -10 divMod:3      -> #(-4 2) because -4*-3 + 2 = -10   
+     -10 divMod:3      -> #(-4 2) because -4*-3 + 2 = -10
      -10 divMod:-3     -> #(3 -1)  because -3*3 + (-1) = -10
 
      1000000000000000000000 divMod:3   -> #(333333333333333333333 1)
@@ -2899,20 +2899,20 @@
     |a b gcd gcd1 u u1 v v1 tmp t swap shift "{SmallInteger}"|
 
     self < tb ifTrue:[
-        a := self.
-        b := tb.
-        swap := false.
+	a := self.
+	b := tb.
+	swap := false.
     ] ifFalse:[
-        a := tb.
-        b := self.
-        swap := true.
+	a := tb.
+	b := self.
+	swap := true.
     ].
 
     shift := ((a lowBit) min:(b lowBit))-1.
     shift > 0 ifTrue:[
-        tmp := shift negated.
-        a := a bitShift:tmp.
-        b := b bitShift:tmp.
+	tmp := shift negated.
+	a := a bitShift:tmp.
+	b := b bitShift:tmp.
     ].
 
     gcd  := a.
@@ -2925,26 +2925,26 @@
     [
 "/      The following condition is true:
 "/        (a * u1) + (b * v1) ~= gcd1 ifTrue:[self halt].
-        t := gcd1 divMod:gcd.
-        gcd1 := gcd.
-        gcd := t at:2.
-        t := t at:1.
-        tmp := v.
+	t := gcd1 divMod:gcd.
+	gcd1 := gcd.
+	gcd := t at:2.
+	t := t at:1.
+	tmp := v.
 "/v1 - (v * t) - v1 + (v * t) ~= 0 ifTrue:[self halt].
-        v := v1 - (v * t).
-        v1 := tmp.
-        tmp := u.
+	v := v1 - (v * t).
+	v1 := tmp.
+	tmp := u.
 "/u1 - (u * t) - u1 + (u * t) ~= 0 ifTrue:[self halt].
-        u := u1 - (u * t).
-        u1 := tmp.
+	u := u1 - (u * t).
+	u1 := tmp.
     gcd > 0] whileTrue.
 
     shift > 0 ifTrue:[
-        gcd1 := gcd1 bitShift:shift.
+	gcd1 := gcd1 bitShift:shift.
     ].
 
     swap ifTrue:[
-        ^ Array with:v1 with:u1 with:gcd1.
+	^ Array with:v1 with:u1 with:gcd1.
     ].
     ^ Array with:u1 with:v1 with:gcd1.
 
@@ -2967,24 +2967,24 @@
     |p i|
 
     (self < 2) ifTrue:[
-        self < 0 ifTrue:[
-            "/
-            "/ requested factorial of a negative number
-            "/
-            ^ self class
-                raise:#domainErrorSignal
-                receiver:self
-                selector:#factorial
-                arguments:#()
-                errorString:'factorial of negative number'
-        ].
-        ^ 1
+	self < 0 ifTrue:[
+	    "/
+	    "/ requested factorial of a negative number
+	    "/
+	    ^ self class
+		raise:#domainErrorSignal
+		receiver:self
+		selector:#factorial
+		arguments:#()
+		errorString:'factorial of negative number'
+	].
+	^ 1
     ].
     p := 2.
     i := 3.
     [i <= self] whileTrue:[
-        p := p * i.
-        i := i + 1.
+	p := p * i.
+	i := i + 1.
     ].
     ^ p
 
@@ -3010,7 +3010,7 @@
      faster and does not suffer from stack overflow problems (with big receivers)."
 
     (self >= 2) ifTrue:[
-        ^ self * (self - 1) factorialR
+	^ self * (self - 1) factorialR
     ].
     ^ 1
 
@@ -3026,12 +3026,12 @@
 
 fib
     "compute the fibionacci number for the receiver.
-        fib(0) := 0
-        fib(1) := 1
-        fib(n) := fib(n-1) + fib(n-2)"
+	fib(0) := 0
+	fib(1) := 1
+	fib(n) := fib(n-1) + fib(n-2)"
 
     self <= 0 ifTrue:[
-        self == 0 ifTrue:[^ 0].
+	self == 0 ifTrue:[^ 0].
     ].
     ^ self fib_helper
 
@@ -3045,10 +3045,10 @@
 fib_helper
     "compute the fibionacci number for the receiver.
 
-        Fib(n) = Fib(n-1) + Fib(n-2)
+	Fib(n) = Fib(n-1) + Fib(n-2)
 
      Knuth:
-        Fib(n+m) = Fib(m) * Fib(n+1) + Fib(m-1) * Fib(n)
+	Fib(n+m) = Fib(m) * Fib(n+1) + Fib(m-1) * Fib(n)
 
      This is about 3 times faster than fib_iterative.
     "
@@ -3058,61 +3058,61 @@
     dict := Dictionary new:100.
 
     fibUsingDict := [:x |
-        |n fib fibN fibNp1 fibNm1 fibXm1 fibXm2 fibXp1|
-
-        x <= 30 ifTrue:[
-                "/ 0 1 2 3 4 5 6  7  8  9 10 11  12  13  14  15  16   17   18   19   20    21    22    23    24    25     26     27     28     29     30
-            fib := #(1 1 2 3 5 8 13 21 34 55 89 144 233 377 610 987 1597 2584 4181 6765 10946 17711 28657 46368 75025 121393 196418 317811 514229 832040
-                     ) at:x
-        ] ifFalse:[
-            fib := dict at:x ifAbsent:nil.
-            fib isNil ifTrue:[
-                fibXm1 := dict at:(x-1) ifAbsent:nil.
-                fibXm1 notNil ifTrue:[
-                    fibXm2 := dict at:(x-2) ifAbsent:nil.
-                    fibXm2 notNil ifTrue:[
-                        fib := fibXm1 + fibXm2.
-                    ] ifFalse:[
-                        fibXp1 := dict at:(x+1) ifAbsent:nil.
-                        fibXp1 notNil ifTrue:[
-                            fib := fibXp1 - fibXm1.
-                        ]
-                    ]
-                ].
-
-                fib isNil ifTrue:[
-                    n := x // 2.
-                    x odd ifTrue:[
-                        "/ m is set to n+1; therefore:
-                        "/ Fib(x) = Fib(n+n+1)      ; x odd; setting n = (x-1)/2
-                        "/ using Knuth:
-                        "/ Fib(n+n+1) = Fib(n+1) * Fib(n+1) + Fib(n+1-1) * Fib(n)
-                        "/            = (Fib(n+1) ^ 2) + (Fib(n) ^ 2)
-                        fibN   := fibUsingDict value:n.
-                        fibNp1 := fibUsingDict value:(n+1).
-                        fib := fibN squared + fibNp1 squared
-                    ] ifFalse:[
-                        "/ as
-                        "/    Fib(n+1) = Fib(n) + Fib(n-1)
-                        "/ therefore:
-                        "/    Fib(n) = Fib(n+1) - Fib(n-1)
-                        "/ and, since n is even, n+1 and n-1 are odd, and can be computed as above.
-                        "/ This gives us:
-                        "/    Fib(x) = Fib(x+1) - Fib(x-1)      ; x even; setting n = x/2
-                        "/           = Fib(n+n+1) - Fib(n+n-1)
-                        "/           = Fib(n+n+1) - Fib((n-1)+(n-1)+1)
-                        "/           = ((Fib(n+1)^2) + (Fib(n)^2)) - ((Fib((n-1)+1)^2) + (Fib((n-1))^2))
-                        "/           = (Fib(n+1)^2) + (Fib(n)^2) - (Fib(n)^2) - (Fib((n-1))^2)
-                        "/           = (Fib(n+1)^2) - (Fib((n-1))^2)
-                        fibNm1 := fibUsingDict value:(n-1).
-                        fibNp1 := fibUsingDict value:(n+1).
-                        fib := fibNp1 squared - fibNm1 squared
-                    ].
-                ].
-                dict at:x put:fib.
-            ]
-        ].
-        fib
+	|n fib fibN fibNp1 fibNm1 fibXm1 fibXm2 fibXp1|
+
+	x <= 30 ifTrue:[
+		"/ 0 1 2 3 4 5 6  7  8  9 10 11  12  13  14  15  16   17   18   19   20    21    22    23    24    25     26     27     28     29     30
+	    fib := #(1 1 2 3 5 8 13 21 34 55 89 144 233 377 610 987 1597 2584 4181 6765 10946 17711 28657 46368 75025 121393 196418 317811 514229 832040
+		     ) at:x
+	] ifFalse:[
+	    fib := dict at:x ifAbsent:nil.
+	    fib isNil ifTrue:[
+		fibXm1 := dict at:(x-1) ifAbsent:nil.
+		fibXm1 notNil ifTrue:[
+		    fibXm2 := dict at:(x-2) ifAbsent:nil.
+		    fibXm2 notNil ifTrue:[
+			fib := fibXm1 + fibXm2.
+		    ] ifFalse:[
+			fibXp1 := dict at:(x+1) ifAbsent:nil.
+			fibXp1 notNil ifTrue:[
+			    fib := fibXp1 - fibXm1.
+			]
+		    ]
+		].
+
+		fib isNil ifTrue:[
+		    n := x // 2.
+		    x odd ifTrue:[
+			"/ m is set to n+1; therefore:
+			"/ Fib(x) = Fib(n+n+1)      ; x odd; setting n = (x-1)/2
+			"/ using Knuth:
+			"/ Fib(n+n+1) = Fib(n+1) * Fib(n+1) + Fib(n+1-1) * Fib(n)
+			"/            = (Fib(n+1) ^ 2) + (Fib(n) ^ 2)
+			fibN   := fibUsingDict value:n.
+			fibNp1 := fibUsingDict value:(n+1).
+			fib := fibN squared + fibNp1 squared
+		    ] ifFalse:[
+			"/ as
+			"/    Fib(n+1) = Fib(n) + Fib(n-1)
+			"/ therefore:
+			"/    Fib(n) = Fib(n+1) - Fib(n-1)
+			"/ and, since n is even, n+1 and n-1 are odd, and can be computed as above.
+			"/ This gives us:
+			"/    Fib(x) = Fib(x+1) - Fib(x-1)      ; x even; setting n = x/2
+			"/           = Fib(n+n+1) - Fib(n+n-1)
+			"/           = Fib(n+n+1) - Fib((n-1)+(n-1)+1)
+			"/           = ((Fib(n+1)^2) + (Fib(n)^2)) - ((Fib((n-1)+1)^2) + (Fib((n-1))^2))
+			"/           = (Fib(n+1)^2) + (Fib(n)^2) - (Fib(n)^2) - (Fib((n-1))^2)
+			"/           = (Fib(n+1)^2) - (Fib((n-1))^2)
+			fibNm1 := fibUsingDict value:(n-1).
+			fibNp1 := fibUsingDict value:(n+1).
+			fib := fibNp1 squared - fibNm1 squared
+		    ].
+		].
+		dict at:x put:fib.
+	    ]
+	].
+	fib
     ].
 
     ^ fibUsingDict value:self
@@ -3149,9 +3149,9 @@
     b := anInteger abs.
 
     a < b ifTrue:[
-        t := a.
-        a := b.
-        b := t.
+	t := a.
+	a := b.
+	b := t.
     ].
 
     b = 0 ifTrue: [^ a].
@@ -3163,9 +3163,9 @@
      3141589999999999 gcd:1000000000000000
 
      Time millisecondsToRun:[
-        10000 timesRepeat:[
-           123456789012345678901234567890 gcd: 9876543210987654321
-        ]
+	10000 timesRepeat:[
+	   123456789012345678901234567890 gcd: 9876543210987654321
+	]
      ]
     "
 
@@ -3177,36 +3177,36 @@
      This is the same as (self log:2) floor."
 
     self <= 0 ifTrue:[
-        ^ self class
-            raise:#domainErrorSignal
-            receiver:self
-            selector:#integerLog2
-            arguments:#()
-            errorString:'logarithm of negative integer'
+	^ self class
+	    raise:#domainErrorSignal
+	    receiver:self
+	    selector:#integerLog2
+	    arguments:#()
+	    errorString:'logarithm of negative integer'
     ].
     ^ self highBit - 1.
 
     "
-      2  log:2  
-      2  integerLog2  
-
-      3  log:2       
-      3  integerLog2  
-
-      4  log:2          
-      4  integerLog2    
-
-      64  integerLog2  
+      2  log:2
+      2  integerLog2
+
+      3  log:2
+      3  integerLog2
+
+      4  log:2
+      4  integerLog2
+
+      64  integerLog2
       100 integerLog2
       100 log:2
       999 integerLog2
       999 log:2
-      120000 integerLog2 
-      120000 log:2       
+      120000 integerLog2
+      120000 log:2
       -1 integerLog2
-      50 factorial integerLog2   
+      50 factorial integerLog2
       50 factorial log:2
-      1000 factorial integerLog2   
+      1000 factorial integerLog2
       1000 factorial log:2       -- float error!!
     "
 !
@@ -3223,12 +3223,12 @@
     result := LargeInteger basicNew numberOfDigits:(b // 8)+1.
     b := b+1.
     [b > 0] whileTrue:[
-        rem >= self ifTrue:[
-            rem := rem -= self.
-            result digitBytes bitSetAt:b.
-        ].
-        rem := rem mul2.
-        b := b - 1.
+	rem >= self ifTrue:[
+	    rem := rem -= self.
+	    result digitBytes bitSetAt:b.
+	].
+	rem := rem mul2.
+	b := b - 1.
     ].
     ^ result compressed.
 
@@ -3247,32 +3247,32 @@
 
 integerSqrt
     "return the largest integer which is less or equal to the
-     receiver's square root. 
+     receiver's square root.
      This might be needed for some number theoretic problems with large numbers
      (and also in cryptography). Uses Newton's method"
 
     |guess prevGuess guessSquared|
 
     self negative ifTrue:[
-        ^ self class
-            raise:#imaginaryResultSignal
-            receiver:self
-            selector:#integerSqrt
-            arguments:#()
-            errorString:'bad (negative) receiver in sqrt'
+	^ self class
+	    raise:#imaginaryResultSignal
+	    receiver:self
+	    selector:#integerSqrt
+	    arguments:#()
+	    errorString:'bad (negative) receiver in sqrt'
     ].
-    
+
     guess := (1 bitShift:(self highBit // 2)).
 
-    [ 
-        prevGuess ~= guess
-        and:[ ((guessSquared := guess squared) - self) abs >= guess ]
+    [
+	prevGuess ~= guess
+	and:[ ((guessSquared := guess squared) - self) abs >= guess ]
     ] whileTrue:[
-        prevGuess := guess.
-        guess := (guess + (self / guess)) // 2.
+	prevGuess := guess.
+	guess := (guess + (self / guess)) // 2.
     ].
     guessSquared > self ifTrue:[
-        guess := guess - 1.
+	guess := guess - 1.
     ].
     "/ self assert:(guess squared <= self).
     "/ self assert:((guess + 1) squared > self).
@@ -3280,14 +3280,14 @@
     ^ guess.
 
     "
-     333 integerSqrt          
-     325 integerSqrt          
-     324 integerSqrt          
-     323 integerSqrt          
+     333 integerSqrt
+     325 integerSqrt
+     324 integerSqrt
+     323 integerSqrt
      10239552311579 integerSqrt
      5397346292805549782720214077673687806275517530364350655459511599582614290 integerSqrt
      1000 factorial integerSqrt
-     
+
      1000 factorial - 1000 factorial integerSqrt squared
      1000 factorial - (1000 factorial integerSqrt + 1) squared
    "
@@ -3306,11 +3306,11 @@
     e := self extendedEuclid:n.
 
     (e at:3) == 1 ifTrue:[
-        ret := e at:1.
-        ret negative ifTrue:[
-            ^ ret + n
-        ].
-        ^ ret.
+	ret := e at:1.
+	ret negative ifTrue:[
+	    ^ ret + n
+	].
+	^ ret.
     ].
 
     ^ 0
@@ -3323,7 +3323,7 @@
      79 inverseMod:3220   -> 1019
      3220 inverseMod:79   -> 54               (54 * 3220) \\ 79
      1234567891 inverseMod:1111111111119
-                          -> 148726663534     (148726663534*1234567891) \\ 1111111111119
+			  -> 148726663534     (148726663534*1234567891) \\ 1111111111119
 
 
      14 extendedEuclid:11
@@ -3356,11 +3356,11 @@
 
     "
      2 to:10000 do:[:n |
-        self assert:((n isPrime and:[ n primeFactors isEmpty])
-                    or:[ n isPrime not and:[n primeFactors product = n]])
+	self assert:((n isPrime and:[ n primeFactors isEmpty])
+		    or:[ n isPrime not and:[n primeFactors product = n]])
      ]
      3 to:10000 do:[:n |
-        self assert:(n factorial primeFactors product = n factorial)
+	self assert:(n factorial primeFactors product = n factorial)
      ]
 
      13195 primeFactors
@@ -3381,9 +3381,9 @@
      1000000000 primeFactors
 
      Time millisecondsToRun:[
-        1000 timesRepeat:[
-            10000000000000000000000000000000000000 primeFactors
-        ]
+	1000 timesRepeat:[
+	    10000000000000000000000000000000000000 primeFactors
+	]
      ]   421
     "
 
@@ -3406,34 +3406,34 @@
     rest := self.
     limit := (rest // 2).
     limitArgOrNil notNil ifTrue:[
-        limit := limit min:limitArgOrNil.
+	limit := limit min:limitArgOrNil.
     ].
 
     "/ try to get the number down fast:
     n := rest lowBit.
     n ~~ 1 ifTrue:[
-        self == 2 ifTrue:[^ #() ].
-        factors add:2 withOccurrences:(n-1).
-        rest := rest rightShift:(n-1).
+	self == 2 ifTrue:[^ #() ].
+	factors add:2 withOccurrences:(n-1).
+	rest := rest rightShift:(n-1).
     ].
 
     checkThisFactor := [:prime |
-            prime*prime > rest ifTrue:[
-                (rest ~~ 1 and:[factors notEmpty]) ifTrue:[ factors add:rest ].
-                ^ factors.
-            ].
-
-            [rest \\ prime == 0] whileTrue:[
-                factors add:prime.
-                rest := rest // prime.
-                rest == 1 ifTrue:[^ factors].
-            ].
-            lastPrime := prime.
-        ].
+	    prime*prime > rest ifTrue:[
+		(rest ~~ 1 and:[factors notEmpty]) ifTrue:[ factors add:rest ].
+		^ factors.
+	    ].
+
+	    [rest \\ prime == 0] whileTrue:[
+		factors add:prime.
+		rest := rest // prime.
+		rest == 1 ifTrue:[^ factors].
+	    ].
+	    lastPrime := prime.
+	].
 
     limit <= 2000 ifTrue:[
-        Integer primesUpTo2000 do:checkThisFactor.
-        ^ factors
+	Integer primesUpTo2000 do:checkThisFactor.
+	^ factors
     ].
 
     "/ actually, all of the code is duplicated; once for primes from a table,
@@ -3446,37 +3446,37 @@
 
     nextTry := lastPrime + 2.
     [ nextTry <= limit ] whileTrue:[
-        "/ now, we are beyond the list of pre-generated primes.
-        "/ change our strategy to: see if it divides an odd number;
-        "/ if so, add the divisor's prime factors.
-        nextTry*nextTry > rest ifTrue:[
-            (rest ~~ 1 and:[factors notEmpty]) ifTrue:[ factors add:rest ].
-            ^ factors.
-        ].
-        [(rest \\ nextTry) == 0] whileTrue:[
-            "/ can only happen relatively late after the last prime,
-            "/ because otherwise, the primeFactors of nextTry would already have
-            "/ been found as divisors.
-            "/ first chance is: (lastPrime + 2) squared
-            nextTry < lastPrime squared ifTrue:[
-                "/ nextTry is a prime !!
-                factors add:nextTry
-            ] ifFalse:[
-                factors addAll:(nextTry primeFactors).
-            ].
-            rest := rest // nextTry.
-        ].
-        nextTry := nextTry + 2.
+	"/ now, we are beyond the list of pre-generated primes.
+	"/ change our strategy to: see if it divides an odd number;
+	"/ if so, add the divisor's prime factors.
+	nextTry*nextTry > rest ifTrue:[
+	    (rest ~~ 1 and:[factors notEmpty]) ifTrue:[ factors add:rest ].
+	    ^ factors.
+	].
+	[(rest \\ nextTry) == 0] whileTrue:[
+	    "/ can only happen relatively late after the last prime,
+	    "/ because otherwise, the primeFactors of nextTry would already have
+	    "/ been found as divisors.
+	    "/ first chance is: (lastPrime + 2) squared
+	    nextTry < lastPrime squared ifTrue:[
+		"/ nextTry is a prime !!
+		factors add:nextTry
+	    ] ifFalse:[
+		factors addAll:(nextTry primeFactors).
+	    ].
+	    rest := rest // nextTry.
+	].
+	nextTry := nextTry + 2.
     ].
     ^ factors
 
     "
      2 to:10000 do:[:n |
-        self assert:((n isPrime and:[ n primeFactors isEmpty])
-                    or:[ n isPrime not and:[n primeFactors product = n]])
+	self assert:((n isPrime and:[ n primeFactors isEmpty])
+		    or:[ n isPrime not and:[n primeFactors product = n]])
      ]
      3 to:10000 do:[:n |
-        self assert:(n factorial primeFactors product = n factorial)
+	self assert:(n factorial primeFactors product = n factorial)
      ]
 
      13195 primeFactors
@@ -3497,9 +3497,9 @@
      1000000000 primeFactors
 
      Time millisecondsToRun:[
-        1000 timesRepeat:[
-            10000000000000000000000000000000000000 primeFactors
-        ]
+	1000 timesRepeat:[
+	    10000000000000000000000000000000000000 primeFactors
+	]
      ]   421
     "
 
@@ -3517,20 +3517,20 @@
     "use the addition chaining algorithm"
 
     exp == 0 ifTrue:[
-        ^ 1
+	^ 1
     ].
     exp == 1 ifTrue:[
-        mod isNumber ifTrue:[
-            ^ self \\ mod.
-        ]
+	mod isNumber ifTrue:[
+	    ^ self \\ mod.
+	]
     ].
     exp negative ifTrue:[
-        ^ self class
-            raise:#domainErrorSignal
-            receiver:self
-            selector:#raisedTo:mod:
-            arguments:(Array with:exp with:mod)
-            errorString:'modulo arithmethic with negative exponent'
+	^ self class
+	    raise:#domainErrorSignal
+	    receiver:self
+	    selector:#raisedTo:mod:
+	    arguments:(Array with:exp with:mod)
+	    errorString:'modulo arithmethic with negative exponent'
     ].
 
     m := mod asModuloNumber.
@@ -3554,10 +3554,10 @@
     bits := exp highBit.
 
     1 to:bits-1 do:[:i|
-        (exp bitAt:i) == 1 ifTrue:[
-            result := m modulusOf:(result * t).
-        ].
-        t := m modulusOf:(t * t).
+	(exp bitAt:i) == 1 ifTrue:[
+	    result := m modulusOf:(result * t).
+	].
+	t := m modulusOf:(t * t).
     ].
     result := m modulusOf:(result * t).
 
@@ -3569,14 +3569,14 @@
      (20000000000000 raisedTo:200) \\ 190
 
       Time millisecondsToRun:[10000 timesRepeat:[
-                                20000000000000 raisedTo:200 mod:190
-                              ]
-                             ]
+				20000000000000 raisedTo:200 mod:190
+			      ]
+			     ]
 
      Time millisecondsToRun:[1000 timesRepeat:[
-                                (20000000000000 raisedTo:200) \\ 190
-                             ]
-                            ]
+				(20000000000000 raisedTo:200) \\ 190
+			     ]
+			    ]
     "
 
     "Created: / 27.4.1999 / 15:19:22 / stefan"
@@ -3608,7 +3608,7 @@
      both p and q, we can use Euler's theorem, expin^phi(m) = 1 (mod m),
      to throw away multiples of phi(p) or phi(q) in e.
      Letting ep = e mod phi(p) and
-              eq = e mod phi(q)
+	      eq = e mod phi(q)
      then combining these two speedups, we only need to evaluate
      p2 = ((expin mod p) ^ ep) mod p and
      q2 = ((expin mod q) ^ eq) mod q.
@@ -3643,7 +3643,7 @@
 
     t := t -= result.
     t < 0 ifTrue:[
-        t := t + q.
+	t := t + q.
     ].
     t := t *= u.
     t := mq modulusOf:t.
@@ -3679,24 +3679,24 @@
     out := 0. shift := 0.
     rest := self.
     [rest > 0] whileTrue:[
-        twoDigits := rest \\ 100.
-        rest := rest // 100.
-        hi := twoDigits // 10.
-        lo := twoDigits \\ 10.
-        out := out bitOr:(((hi bitShift:4)+lo) bitShift:shift).
-        shift := shift + 8.
+	twoDigits := rest \\ 100.
+	rest := rest // 100.
+	hi := twoDigits // 10.
+	lo := twoDigits \\ 10.
+	out := out bitOr:(((hi bitShift:4)+lo) bitShift:shift).
+	shift := shift + 8.
     ].
 
     ^ out
 
     "
      (100 factorial) asBCD
-     999999999 asBCD 
-     100000000 asBCD   
-     123456789 asBCD   
-     99999999 asBCD  
+     999999999 asBCD
+     100000000 asBCD
+     123456789 asBCD
+     99999999 asBCD
      12345678 asBCD
-     12345678 asBCD 
+     12345678 asBCD
      12345678 asBCD hexPrintString
      12345678901234567890 asBCD
     "
@@ -3713,7 +3713,7 @@
     |s rest twoDigits hi lo|
 
     self == 0 ifTrue:[
-        ^ #[ 16r00 ]
+	^ #[ 16r00 ]
     ].
 
     "/ a very rough estimate on the final size ...
@@ -3721,17 +3721,17 @@
 
     rest := self.
     [rest > 0] whileTrue:[
-        twoDigits := rest \\ 100.
-        rest := rest // 100.
-        hi := twoDigits \\ 10.
-        lo := twoDigits // 10.
-        s nextPut:(lo bitShift:4)+hi
+	twoDigits := rest \\ 100.
+	rest := rest // 100.
+	hi := twoDigits \\ 10.
+	lo := twoDigits // 10.
+	s nextPut:(lo bitShift:4)+hi
     ].
 
     ^ s contents reverse
 
     "
-     12345678 asBCDBytes 
+     12345678 asBCDBytes
      12345678 asBCDBytes hexPrintString
      12345678901234567890 asBCDBytes
     "
@@ -3786,21 +3786,21 @@
 
     base := b.
     (base isInteger and:[ base between:2 and:36 ]) ifFalse:[
-        ConversionError raiseRequestWith:self errorString:' - invalid base: ', base printString.
-        base := 10.
+	ConversionError raiseRequestWith:self errorString:' - invalid base: ', base printString.
+	base := 10.
     ].
 
     showRadix ifTrue:[
-        base printOn:aStream.
-        aStream nextPut:$r.
+	base printOn:aStream.
+	aStream nextPut:$r.
     ].
 
     (self = 0) ifTrue:[aStream nextPut:$0. ^ self].
     (self negative) ifTrue:[
-        aStream nextPut:$- .
-        num := self negated.
+	aStream nextPut:$- .
+	num := self negated.
     ] ifFalse:[
-        num := self.
+	num := self.
     ].
 
     "
@@ -3824,17 +3824,17 @@
     r2 := base*base.   "/ radix^2
     r4 := r2*r2.        "/ radix^4
     base <= 10 ifTrue:[
-        r := r4*r2.     "/ radix^6 (chunks of 6 digits)
-        nD := 6.
+	r := r4*r2.     "/ radix^6 (chunks of 6 digits)
+	nD := 6.
     ] ifFalse:[
-        r := r4*base.    "/ radix^5 (chunks of 5 digits)
-        nD := 5.
+	r := r4*base.    "/ radix^5 (chunks of 5 digits)
+	nD := 5.
     ].
     SmallInteger maxBits >= 63 ifTrue:[
-        r := r*r.    "/ radix^10 / radix^12 (chunks of 10/12 digits)
-        nD := nD * 2.
+	r := r*r.    "/ radix^10 / radix^12 (chunks of 10/12 digits)
+	nD := nD * 2.
     ].
-   
+
     "get a Stream with space for the digits we are going to print.
      We need ((num log:base) ceiling) digits, which is equivalent
      to ((num log:2)/(base log:2) ceiling)
@@ -3842,40 +3842,40 @@
     s := WriteStream on:(String new:10).
 
     [num >= r] whileTrue:[
-        "/
-        "/ chop off nD digits.
-        "/
-        divMod := num divMod:r.
-        num := divMod at:1.
-        numN := divMod at:2.
-
-        "/ process them
-        nD timesRepeat:[
-            divMod := numN divMod:base.
-            numN := divMod at:1.
-            mod := divMod at:2.
-            s nextPut:(Character digitValue:mod).
-        ].
+	"/
+	"/ chop off nD digits.
+	"/
+	divMod := num divMod:r.
+	num := divMod at:1.
+	numN := divMod at:2.
+
+	"/ process them
+	nD timesRepeat:[
+	    divMod := numN divMod:base.
+	    numN := divMod at:1.
+	    mod := divMod at:2.
+	    s nextPut:(Character digitValue:mod).
+	].
     ].
 
     [num ~= 0] whileTrue:[
-        divMod := num divMod:base.
-        num := divMod at:1.
-        mod := divMod at:2.
-        s nextPut:(Character digitValue:mod).
+	divMod := num divMod:base.
+	num := divMod at:1.
+	mod := divMod at:2.
+	s nextPut:(Character digitValue:mod).
     ].
 
     aStream nextPutAll:(s contents reverse).
 
     "
-        3000 factorial printOn:Transcript base:10
-        10 printOn:Transcript base:3
-        31 printOn:Transcript base:3
-        10 printOn:Transcript base:2
-        31 printOn:Transcript base:2
-        -20  printOn:Transcript base:16
-        -20  printOn:Transcript base:10
-        Time millisecondsToRun:[10000 factorial printString] 610  7650
+	3000 factorial printOn:Transcript base:10
+	10 printOn:Transcript base:3
+	31 printOn:Transcript base:3
+	10 printOn:Transcript base:2
+	31 printOn:Transcript base:2
+	-20  printOn:Transcript base:16
+	-20  printOn:Transcript base:10
+	Time millisecondsToRun:[10000 factorial printString] 610  7650
     "
 
     "Modified: / 20-01-1998 / 18:05:02 / stefan"
@@ -3883,7 +3883,7 @@
     "Modified: / 02-08-2010 / 12:24:14 / cg"
 !
 
-printOn:aStream base:baseInteger size:sz 
+printOn:aStream base:baseInteger size:sz
     "print a string representation of the receiver in the specified
      base. The string is padded on the left with fillCharacter to make
      its size as specified in sz."
@@ -3909,7 +3909,7 @@
     string := stream contents.
     actualSize := string size.
     actualSize < sz ifTrue:[
-        aStream next:sz-actualSize put:fillCharacter.
+	aStream next:sz-actualSize put:fillCharacter.
     ].
     aStream nextPutAll:string.
 
@@ -3947,10 +3947,10 @@
 
     "test all between 1 and 9999:
       1 to:9999 do:[:n |
-        |romanString|
-
-        romanString := String streamContents:[:stream | n printRomanOn:stream].
-        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
+	|romanString|
+
+	romanString := String streamContents:[:stream | n printRomanOn:stream].
+	(Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
      ]
     "
 !
@@ -3968,46 +3968,46 @@
     restValue > 0 ifFalse:[self error:'negative roman'].
 
     naive ifTrue:[
-        spec := #(
-                " value string repeat "
-                   1000 'M'    true
-                    500 'D'    false
-                    100 'C'    true
-                     50 'L'    false
-                     10 'X'    true
-                      5 'V'    false
-                      1 'I'    true
-                 ).
+	spec := #(
+		" value string repeat "
+		   1000 'M'    true
+		    500 'D'    false
+		    100 'C'    true
+		     50 'L'    false
+		     10 'X'    true
+		      5 'V'    false
+		      1 'I'    true
+		 ).
     ] ifFalse:[
-        spec := #(
-                " value string repeat "
-                   1000 'M'    true
-                    900 'CM'   false
-                    500 'D'    false
-                    400 'CD'   false
-                    100 'C'    true
-                     90 'XC'   false
-                     50 'L'    false
-                     40 'XL'   false
-                     10 'X'    true
-                      9 'IX'   false
-                      5 'V'    false
-                      4 'IV'   false
-                      1 'I'    true
-                 ).
+	spec := #(
+		" value string repeat "
+		   1000 'M'    true
+		    900 'CM'   false
+		    500 'D'    false
+		    400 'CD'   false
+		    100 'C'    true
+		     90 'XC'   false
+		     50 'L'    false
+		     40 'XL'   false
+		     10 'X'    true
+		      9 'IX'   false
+		      5 'V'    false
+		      4 'IV'   false
+		      1 'I'    true
+		 ).
     ].
 
     spec
-        inGroupsOf:3
-        do:[:rValue :rString :repeatFlag |
-
-            [
-                (restValue >= rValue) ifTrue:[
-                    aStream nextPutAll:rString.
-                    restValue := restValue - rValue.
-                ].
-            ] doWhile:[ repeatFlag and:[ restValue >= rValue] ].
-        ].
+	inGroupsOf:3
+	do:[:rValue :rString :repeatFlag |
+
+	    [
+		(restValue >= rValue) ifTrue:[
+		    aStream nextPutAll:rString.
+		    restValue := restValue - rValue.
+		].
+	    ] doWhile:[ repeatFlag and:[ restValue >= rValue] ].
+	].
 
     "
      1 to:10 do:[:i | i printRomanOn:Transcript naive:false. Transcript cr.].
@@ -4019,19 +4019,19 @@
 
     "test all between 1 and 9999:
       1 to:9999 do:[:n |
-        |romanString|
-
-        romanString := String streamContents:[:stream | n printRomanOn:stream naive:false].
-        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
+	|romanString|
+
+	romanString := String streamContents:[:stream | n printRomanOn:stream naive:false].
+	(Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
      ]
     "
 
     "test naive all between 1 and 9999:
       1 to:9999 do:[:n |
-        |romanString|
-
-        romanString := String streamContents:[:stream | n printRomanOn:stream naive:true].
-        (Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
+	|romanString|
+
+	romanString := String streamContents:[:stream | n printRomanOn:stream naive:true].
+	(Integer readFromRomanString:romanString onError:nil) ~= n ifTrue:[self halt].
      ]
     "
 !
@@ -4040,12 +4040,12 @@
     "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
 
     "
-     10 printStringRadix:16   
+     10 printStringRadix:16
     "
 
     "Created: / 19-01-1998 / 17:20:58 / stefan"
@@ -4064,7 +4064,7 @@
     s := self printStringRadix:aRadix.
     actualSize := s size.
     actualSize < sz ifTrue:[
-        s := ((String new:(sz - actualSize)) atAllPut:fillCharacter) , s
+	s := ((String new:(sz - actualSize)) atAllPut:fillCharacter) , s
     ].
     ^ s
 
@@ -4151,17 +4151,17 @@
 
     "
      self assert:( 1.0 exponent = 1 exponent ).
-     self assert:( 2.0 exponent = 2 exponent ).  
-     self assert:( 3.0 exponent = 3 exponent ).  
-     self assert:( 4.0 exponent = 4 exponent ).  
-     self assert:( 12345.0 exponent = 12345 exponent ).  
-     self assert:( 0.0 exponent = 0 exponent ).   
+     self assert:( 2.0 exponent = 2 exponent ).
+     self assert:( 3.0 exponent = 3 exponent ).
+     self assert:( 4.0 exponent = 4 exponent ).
+     self assert:( 12345.0 exponent = 12345 exponent ).
+     self assert:( 0.0 exponent = 0 exponent ).
 
      self assert:( -1.0 exponent = -1 exponent ).
-     self assert:( -2.0 exponent = -2 exponent ).  
-     self assert:( -3.0 exponent = -3 exponent ).  
-     self assert:( -4.0 exponent = -4 exponent ).  
-     self assert:( -12345.0 exponent = -12345 exponent ).  
+     self assert:( -2.0 exponent = -2 exponent ).
+     self assert:( -3.0 exponent = -3 exponent ).
+     self assert:( -4.0 exponent = -4 exponent ).
+     self assert:( -12345.0 exponent = -12345 exponent ).
     "
 !
 
@@ -4181,38 +4181,38 @@
 isPerfectSquare
     "return true if I am a perfect square.
      That is a number for which the square root is an integer."
-     
+
     |intSqrt realSqrt|
-    
+
     self strictlyPositive ifFalse:[
-        self == 0 ifTrue:[^ true].
-        "/ should we raise a domain error for negative receivers?
-        ^ false
+	self == 0 ifTrue:[^ true].
+	"/ should we raise a domain error for negative receivers?
+	^ false
     ].
 
     "/ q&d check for common small squares
-    self < 400 ifTrue:[    
-        ^ #(1 4 9 16 25 36 49 64 81 100 121 144 169 196 225 256 289 324 361 ) includes:self.
-    ].        
-    self < 1024 ifTrue:[    
-        ^ #(400 441 484 529 576 625 676 729 784 841 900 961) includes:self.
+    self < 400 ifTrue:[
+	^ #(1 4 9 16 25 36 49 64 81 100 121 144 169 196 225 256 289 324 361 ) includes:self.
     ].
-    
+    self < 1024 ifTrue:[
+	^ #(400 441 484 529 576 625 676 729 784 841 900 961) includes:self.
+    ].
+
     "/ try powers of 2
     self isPowerOfTwo ifTrue:[
-        ^ self lowBit odd
+	^ self lowBit odd
     ].
-    
+
     "/ guess
     realSqrt := self sqrt.
     realSqrt isFinite ifTrue:[
-        realSqrt = realSqrt truncated ifTrue:[
-            "/ still have to check due to rounding errors.
-            intSqrt := realSqrt truncated asInteger.
-            ^ intSqrt squared = self
-        ].    
+	realSqrt = realSqrt truncated ifTrue:[
+	    "/ still have to check due to rounding errors.
+	    intSqrt := realSqrt truncated asInteger.
+	    ^ intSqrt squared = self
+	].
     ].
-    
+
     "/ slow code
     intSqrt := self integerSqrt.
     ^ intSqrt squared = self
@@ -4239,14 +4239,14 @@
 
     "/ the following is a q&d hack, using existing code.
     ^ (Integer
-        readFromString:(self printStringRadix:p)
-        radix:2
-        onError:-1) isPowerOfTwo
+	readFromString:(self printStringRadix:p)
+	radix:2
+	onError:-1) isPowerOfTwo
 
     "
      0 isPowerOf:2
      1 isPowerOf:2
-     
+
      16r0000000000000000 isPowerOf:2
      16r0000004000000000 isPowerOf:2
      16r0000004000000001 isPowerOf:2
@@ -4292,17 +4292,17 @@
     maxBytes := self digitLength.
     (self digitAt:maxBytes) isPowerOfTwo ifFalse:[^ false].
     1 to:maxBytes-1 do:[:byteIndex |
-        (self digitAt:byteIndex) ~~ 0 ifTrue:[^ false].
+	(self digitAt:byteIndex) ~~ 0 ifTrue:[^ false].
     ].
     ^ true
 
     "
-     10000 factorial isPowerOfTwo  
-     |n| n := 10000 factorial. Time millisecondsToRun:[1000 timesRepeat:[ n isPowerOfTwo]] 
-    "
-    "
-     (2 raisedTo:10000) isPowerOfTwo  
-     |n| n := (2 raisedTo:10000). Time millisecondsToRun:[1000 timesRepeat:[ n isPowerOfTwo]] 
+     10000 factorial isPowerOfTwo
+     |n| n := 10000 factorial. Time millisecondsToRun:[1000 timesRepeat:[ n isPowerOfTwo]]
+    "
+    "
+     (2 raisedTo:10000) isPowerOfTwo
+     |n| n := (2 raisedTo:10000). Time millisecondsToRun:[1000 timesRepeat:[ n isPowerOfTwo]]
     "
 
     "Modified: / 20-06-2011 / 12:43:05 / cg"
@@ -4326,19 +4326,19 @@
     "/      Integer initializePrimeCacheUpTo:1000000
     "/ and when done, cleanup with flushPrimeCache
     self <= (PrimeCache size*2) ifTrue:[
-        ^ PrimeCache at:self//2.
+	^ PrimeCache at:self//2.
     ].
 
     limit := self sqrt.
 
     firstFewPrimes := self class primesUpTo2000.
     firstFewPrimes do:[:p |
-        p > limit ifTrue:[^ true].
-        (self \\ p) == 0 ifTrue:[ ^ false ].
+	p > limit ifTrue:[^ true].
+	(self \\ p) == 0 ifTrue:[ ^ false ].
     ].
 
     (firstFewPrimes last+2) to:limit by:2 do:[:i |
-        (self \\ i) == 0 ifTrue:[ ^ false ].
+	(self \\ i) == 0 ifTrue:[ ^ false ].
     ].
     ^ true
 
@@ -4363,13 +4363,13 @@
     ^ self + (n - rest)
 
     "
-     1 nextMultipleOf: 4  
-     2 nextMultipleOf: 4  
-     3 nextMultipleOf: 4  
-     4 nextMultipleOf: 4  
-     5 nextMultipleOf: 4  
-
-     22 nextMultipleOf: 4 
+     1 nextMultipleOf: 4
+     2 nextMultipleOf: 4
+     3 nextMultipleOf: 4
+     4 nextMultipleOf: 4
+     5 nextMultipleOf: 4
+
+     22 nextMultipleOf: 4
     "
 !
 
@@ -4377,7 +4377,7 @@
     "return the power of 2 at or above the receiver.
      Useful for padding.
      Notice, that for a powerOf2, the receiver is returned.
-     Also notice, that (because it is used for padding), 
+     Also notice, that (because it is used for padding),
      0 is returned for zero."
 
     |x t sh|
@@ -4389,36 +4389,36 @@
     x := x bitOr: (x bitShift: -8).
     x := x bitOr: (t := x bitShift: -16).
     t == 0 ifFalse:[
-        sh := -32.
-        [
-            x := x bitOr: (t := x bitShift: sh).
-            sh := sh + sh. 
-        ] doWhile: [t ~~ 0]
+	sh := -32.
+	[
+	    x := x bitOr: (t := x bitShift: sh).
+	    sh := sh + sh.
+	] doWhile: [t ~~ 0]
     ].
-    ^ x + 1 
-
-    "
-     0 nextPowerOf2    
-     1 nextPowerOf2    
-     2 nextPowerOf2    
-     3 nextPowerOf2    
-     4 nextPowerOf2    
-     5 nextPowerOf2    
-     6 nextPowerOf2    
-     7 nextPowerOf2    
-     8 nextPowerOf2    
+    ^ x + 1
+
+    "
+     0 nextPowerOf2
+     1 nextPowerOf2
+     2 nextPowerOf2
+     3 nextPowerOf2
+     4 nextPowerOf2
+     5 nextPowerOf2
+     6 nextPowerOf2
+     7 nextPowerOf2
+     8 nextPowerOf2
 
      22 nextPowerOf2
-     12 factorial nextPowerOf2  isPowerOf:2  
-     100 factorial nextPowerOf2  isPowerOf:2  
+     12 factorial nextPowerOf2  isPowerOf:2
+     100 factorial nextPowerOf2  isPowerOf:2
      1000 factorial nextPowerOf2  isPowerOf:2
      Time millisecondsToRun:[
-         |v|
-         v := 1000 factorial.
-         1000 timesRepeat:[
-            v nextPowerOf2    
-         ]    
-     ]    
+	 |v|
+	 v := 1000 factorial.
+	 1000 timesRepeat:[
+	    v nextPowerOf2
+	 ]
+     ]
     "
 !
 
@@ -4430,10 +4430,10 @@
     num := self + 1.
     num <= 2 ifTrue:[^ 2].
     num even ifTrue:[
-        num := num + 1
+	num := num + 1
     ].
     [num isPrime] whileFalse:[
-        num := num + 2
+	num := num + 2
     ].
     ^ num
 
@@ -4457,32 +4457,32 @@
     ^ self bitCount odd
 
     "
-     0 parityOdd    
-     1 parityOdd    
-     2 parityOdd    
-     4 parityOdd    
-     5 parityOdd    
-     7 parityOdd    
-     33 parityOdd   
-     6 parityOdd    
+     0 parityOdd
+     1 parityOdd
+     2 parityOdd
+     4 parityOdd
+     5 parityOdd
+     7 parityOdd
+     33 parityOdd
+     6 parityOdd
 
      1 to:1000000 do:[:n |
-        self assert:(n parityOdd = ((n printStringRadix:2) occurrencesOf:$1) odd).
+	self assert:(n parityOdd = ((n printStringRadix:2) occurrencesOf:$1) odd).
      ]
 
      0 to:255 do:[:n |
-        |p|
-
-        p := 
-            (((((((((n rightShift: 7) 
-            bitXor: (n rightShift: 6)) 
-                bitXor: (n rightShift: 5))
-                    bitXor: (n rightShift: 4))
-                        bitXor: (n rightShift: 3))
-                            bitXor: (n rightShift: 2))
-                                bitXor: (n rightShift: 1))
-                                    bitXor: n) bitAnd:1) == 1.
-        self assert:(n parityOdd = p).
+	|p|
+
+	p :=
+	    (((((((((n rightShift: 7)
+	    bitXor: (n rightShift: 6))
+		bitXor: (n rightShift: 5))
+		    bitXor: (n rightShift: 4))
+			bitXor: (n rightShift: 3))
+			    bitXor: (n rightShift: 2))
+				bitXor: (n rightShift: 1))
+				    bitXor: n) bitAnd:1) == 1.
+	self assert:(n parityOdd = p).
      ]
     "
 
@@ -4493,7 +4493,7 @@
 !Integer methodsFor:'special modulo arithmetic'!
 
 add_32:anInteger
-    "return a C-semantic 32bit sum of the receiver and the argument. 
+    "return a C-semantic 32bit sum of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns a signed 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of
@@ -4503,16 +4503,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 + val2;
     RETURN(__MKINT(rslt));
@@ -4523,7 +4523,7 @@
 !
 
 add_32u:anInteger
-    "return a C-semantic 32bit unsigned sum of the receiver and the argument. 
+    "return a C-semantic 32bit unsigned sum of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns an unsigned 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of
@@ -4533,16 +4533,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 + val2;
     RETURN(__MKUINT((unsigned)rslt));
@@ -4553,7 +4553,7 @@
 !
 
 mul_32:anInteger
-    "return a C-semantic 32bit product of the receiver and the argument. 
+    "return a C-semantic 32bit product of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns a signed 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of
@@ -4563,16 +4563,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 * val2;
     RETURN(__MKINT(rslt));
@@ -4583,7 +4583,7 @@
 !
 
 mul_32u:anInteger
-    "return a C-semantic 32bit unsigned product of the receiver and the argument. 
+    "return a C-semantic 32bit unsigned product of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns an unsigned 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of
@@ -4593,16 +4593,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 * val2;
     RETURN(__MKUINT((unsigned)rslt));
@@ -4613,7 +4613,7 @@
 !
 
 sub_32:anInteger
-    "return a C-semantic 32bit difference of the receiver and the argument. 
+    "return a C-semantic 32bit difference of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns a signed 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of
@@ -4623,16 +4623,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 - val2;
     RETURN(__MKINT(rslt));
@@ -4643,7 +4643,7 @@
 !
 
 sub_32u:anInteger
-    "return a C-semantic 32bit unsigned difference of the receiver and the argument. 
+    "return a C-semantic 32bit unsigned difference of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns an unsigned 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of
@@ -4653,16 +4653,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 - val2;
     RETURN(__MKUINT((unsigned)rslt));
@@ -4686,7 +4686,7 @@
      convert C/Java numbers."
 
     self < 0 ifTrue:[
-        ^ 16r100000000 + self
+	^ 16r100000000 + self
     ].
     ^ self
 
@@ -4704,7 +4704,7 @@
      convert C/Java numbers."
 
     self < 0 ifTrue:[
-        ^ 16r10000000000000000 + self
+	^ 16r10000000000000000 + self
     ].
     ^ self
 
@@ -4729,16 +4729,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 & val2;
     RETURN(__MKINT(rslt));
@@ -4759,16 +4759,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 & val2;
     RETURN(__MKUINT(rslt));
@@ -4789,10 +4789,10 @@
     int val, rslt;
 
     if (__isSmallInteger(self)) {
-        val = __intVal(self);
+	val = __intVal(self);
     } else {
-        val = __longIntVal(self);
-        if (!val) goto bad;
+	val = __longIntVal(self);
+	if (!val) goto bad;
     }
     rslt = ~val;
     RETURN(__MKINT(rslt));
@@ -4813,10 +4813,10 @@
     int val, rslt;
 
     if (__isSmallInteger(self)) {
-        val = __intVal(self);
+	val = __intVal(self);
     } else {
-        val = __longIntVal(self);
-        if (!val) goto bad;
+	val = __longIntVal(self);
+	if (!val) goto bad;
     }
     rslt = ~val;
     RETURN(__MKUINT(rslt));
@@ -4837,16 +4837,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 | val2;
     RETURN(__MKINT(rslt));
@@ -4867,16 +4867,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 | val2;
     RETURN(__MKUINT(rslt));
@@ -4897,16 +4897,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 ^ val2;
     RETURN(__MKINT(rslt));
@@ -4927,16 +4927,16 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     }
     rslt = val1 ^ val2;
     RETURN(__MKUINT(rslt));
@@ -5065,7 +5065,7 @@
 copyright
 "
  COPYRIGHT (c) 1999 by eXept Software AG
-              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
@@ -5083,31 +5083,31 @@
     (with big numbers, this does make a difference)
 
     WARNING: this does only work with numbers which have no common
-             divisor (which is true for cryptographic applications).
-             So, use this only if you know what you are doing ...
+	     divisor (which is true for cryptographic applications).
+	     So, use this only if you know what you are doing ...
 
     [author:]
-        Stefan Vogel
+	Stefan Vogel
 
     [see also:]
-        Integer SmallInteger LargeInsteger
+	Integer SmallInteger LargeInsteger
 
     [instance variables:]
-        modulus       the modulus
-        reciprocal    reciprocal of the modulus
-        shift         shift count to cut off some bits
+	modulus       the modulus
+	reciprocal    reciprocal of the modulus
+	shift         shift count to cut off some bits
 "
 !
 
 examples
 "
-                                                                [exBegin]
-        17 asModuloNumber modulusOf:38
-                                                                [exEnd]
-
-                                                                [exBegin]
-        38 \\ 17
-                                                                [exEnd]
+								[exBegin]
+	17 asModuloNumber modulusOf:38
+								[exEnd]
+
+								[exBegin]
+	38 \\ 17
+								[exEnd]
 "
 ! !
 
@@ -5161,12 +5161,12 @@
     "this subtract is done max 2 times"
     cnt := 2.
     [(t := e - modulus) >= 0] whileTrue:[
-        e := t.
-        cnt == 0 ifTrue:[
-            "shortcut didn't work, do it the long way"
-            ^ e \\ modulus.
-        ].
-        cnt := cnt - 1.
+	e := t.
+	cnt == 0 ifTrue:[
+	    "shortcut didn't work, do it the long way"
+	    ^ e \\ modulus.
+	].
+	cnt := cnt - 1.
     ].
     ^ e.
 
@@ -5189,9 +5189,9 @@
 
      m := 123456789901398721398721931729371293712943794254034548369328469438562948623498659238469234659823469823658423659823658.
      Time millisecondsToRun:[
-        100000 timesRepeat:[
-            874928459437598375937451931729371293712943794254034548369328469438562948623498659238469234659823469823658423659823658 \\ m
-        ]
+	100000 timesRepeat:[
+	    874928459437598375937451931729371293712943794254034548369328469438562948623498659238469234659823469823658423659823658 \\ m
+	]
      ]
     "