Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Fri, 24 Jul 2015 08:06:37 +0100
branchjv
changeset 18630 a74d669db937
parent 18617 fbfd2d411738 (current diff)
parent 18629 b38434722f21 (diff)
child 18631 27ffa826691b
Merge
CharacterEncoder.st
CharacterEncoderImplementations__ISO10646_to_UTF8.st
LargeInteger.st
Method.st
Object.st
ProcessorScheduler.st
Registry.st
String.st
Symbol.st
UnixOperatingSystem.st
WeakArray.st
WeakDependencyDictionary.st
WeakIdentityDictionary.st
WeakIdentitySet.st
WeakValueDictionary.st
Win32OperatingSystem.st
--- a/CharacterEncoder.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/CharacterEncoder.st	Fri Jul 24 08:06:37 2015 +0100
@@ -1327,12 +1327,14 @@
 encodeString:aUnicodeString
     "given a string in unicode, return a string in my encoding for it"
 
-    |newString myCode uniCodePoint bits|
+    |newString myCode uniCodePoint bits 
+     stringSize "{ Class: SmallInteger }"|
 
-    newString := String new:(aUnicodeString size).
+    stringSize := aUnicodeString size.
+    newString := String new:stringSize.
     bits := newString bitsPerCharacter.
 
-    1 to:aUnicodeString size do:[:idx |
+    1 to:stringSize do:[:idx |
         uniCodePoint := (aUnicodeString at:idx) codePoint.
         myCode := self encode:uniCodePoint.
         myCode > 16rFF ifTrue:[
@@ -1739,11 +1741,11 @@
 !CharacterEncoder class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoder.st,v 1.139 2015-04-29 11:21:18 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoder.st,v 1.139 2015-04-29 11:21:18 cg Exp $'
+    ^ '$Header$'
 ! !
 
 
--- a/CharacterEncoderImplementations__ISO10646_to_UTF8.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/CharacterEncoderImplementations__ISO10646_to_UTF8.st	Fri Jul 24 08:06:37 2015 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2004 by eXept Software AG
 	      All Rights Reserved
@@ -54,7 +52,7 @@
   Decoding (utf8 to unicode):
      |t|
 
-     t := ISO10646_to_UTF8 encodeString:'Helloœ'.
+     t := ISO10646_to_UTF8 encodeString:'Helloœ'.
      ISO10646_to_UTF8 decodeString:t.
 "
 ! !
@@ -348,20 +346,23 @@
      If you work a lot with utf8 encoded textFiles,
      this is a first-class candidate for a primitive."
 
-    |s|
+    |s
+     stringSize "{ Class: SmallInteger }"|
 
     "/ avoid creation of new strings if possible
     aUnicodeString containsNon7BitAscii ifFalse:[
         ^ aUnicodeString asSingleByteString
     ].
 
-    s := WriteStream on:(String uninitializedNew:(aUnicodeString size * 3 // 2)).
-    aUnicodeString do:[:eachCharacter |
-        |codePoint "{Class: SmallInteger }" b1 b2 b3 b4 b5 v "{Class: SmallInteger }"|
+    stringSize := aUnicodeString size.
+    s := WriteStream on:(String uninitializedNew:(stringSize * 3 // 2)).
+    1 to:stringSize do:[:idx |
+        |character codePoint "{Class: SmallInteger }" b1 b2 b3 b4 b5 v "{Class: SmallInteger }"|
 
-        codePoint := eachCharacter codePoint.
+        character := aUnicodeString at:idx.
+        codePoint := character codePoint.
         codePoint <= 16r7F ifTrue:[
-            s nextPut:eachCharacter.
+            s nextPut:character.
         ] ifFalse:[
             b1 := Character value:((codePoint bitAnd:16r3F) bitOr:2r10000000).
             v := codePoint bitShift:-6.
@@ -394,7 +395,7 @@
                                 s nextPut:b5; nextPut:b4; nextPut:b3; nextPut:b2; nextPut:b1.
                             ] ifFalse:[
                                 "/ cannot happen - we only support up to 30 bit characters
-                                EncodingError raiseWith:eachCharacter errorString:'codePoint > 31bit in #utf8Encode'.
+                                EncodingError raiseWith:character errorString:'codePoint > 31bit in #utf8Encode'.
                             ]
                         ].
                     ].
--- a/LargeInteger.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/LargeInteger.st	Fri Jul 24 08:06:37 2015 +0100
@@ -341,14 +341,14 @@
      Use a special method for this case ...
     "
     ((numberClass := aNumber class) == SmallInteger) ifTrue:[
-        ^ self productFromInteger:aNumber
+	^ self productFromInteger:aNumber
     ].
 
     "
      if the argument is not a largeInteger, coerce
     "
     (numberClass == self class) ifFalse:[
-        ^ self retry:#* coercing:aNumber
+	^ self retry:#* coercing:aNumber
     ].
 
     otherSign := aNumber sign.
@@ -498,12 +498,12 @@
      The result is truncated toward negative infinity
      and will be negative, if the operands signs differ.
      The following is always true:
-        (receiver // aNumber) * aNumber + (receiver \\ aNumber) = receiver
+	(receiver // aNumber) * aNumber + (receiver \\ aNumber) = receiver
 
      Be careful with negative results: 9 // 4 -> 2, while -9 // 4 -> -3.
      Especially surprising:
-        -1 // 10 -> -1 (because -(1/10) is truncated towards next smaller integer, which is -1.
-        -10 // 3 -> -4 (because -(10/3) is truncated towards next smaller integer, which is -4.
+	-1 // 10 -> -1 (because -(1/10) is truncated towards next smaller integer, which is -1.
+	-10 // 3 -> -4 (because -(10/3) is truncated towards next smaller integer, which is -4.
 
      See #quo: which returns -2 in the above case and #rem: which is the corresponding remainder."
 
@@ -517,38 +517,38 @@
      Use a special method for this case ...
     "
     (cls == SmallInteger) ifTrue:[
-        abs := aNumber.
-        abs := abs abs.
-        (abs between:1 and:(SmallInteger maxBytes == 8 ifTrue:16r00ffffffffff ifFalse:16r00ffffff)) ifTrue:[
-            divMod := self absFastDivMod:abs.
-        ] ifFalse:[
-            n := abs asLargeInteger.
-        ].
+	abs := aNumber.
+	abs := abs abs.
+	(abs between:1 and:(SmallInteger maxBytes == 8 ifTrue:16r00ffffffffff ifFalse:16r00ffffff)) ifTrue:[
+	    divMod := self absFastDivMod:abs.
+	] ifFalse:[
+	    n := abs asLargeInteger.
+	].
     ] ifFalse:[
-        "
-         if the argument is not a largeInteger, coerce
-        "
-        (cls == self class) ifFalse:[
-            ^ self retry:#// coercing:aNumber
-        ].
-        n := aNumber
+	"
+	 if the argument is not a largeInteger, coerce
+	"
+	(cls == self class) ifFalse:[
+	    ^ self retry:#// coercing:aNumber
+	].
+	n := aNumber
     ].
 
     divMod isNil ifTrue:[
-        divMod := self absDivMod:n.
+	divMod := self absDivMod:n.
     ].
     quo := divMod at:1.
     (sign == aNumber sign) ifFalse:[
-        "/ adjust for truncation if negative and there is a remainder ...
-        "/ be careful: there is one special case to care for here:
-        "/ if quo is maxInt+1, the negation can be represented as a smallInt.
-        quo := quo setSign:-1.
-        (divMod at:2) == 0 ifFalse:[
-            ^ quo - 1
-        ].
-        quo digitLength == SmallInteger maxBytes ifTrue:[
-            ^ quo compressed
-        ].
+	"/ adjust for truncation if negative and there is a remainder ...
+	"/ be careful: there is one special case to care for here:
+	"/ if quo is maxInt+1, the negation can be represented as a smallInt.
+	quo := quo setSign:-1.
+	(divMod at:2) == 0 ifFalse:[
+	    ^ quo - 1
+	].
+	quo digitLength == SmallInteger maxBytes ifTrue:[
+	    ^ quo compressed
+	].
     ].
     ^ quo
 
@@ -586,14 +586,14 @@
 
      The returned remainder has the same sign as aNumber.
      The following is always true:
-        (receiver // aNumber) * aNumber + (receiver \\ aNumber) = receiver
+	(receiver // aNumber) * aNumber + (receiver \\ aNumber) = 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.
+	-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.
 
      See #rem: which is the corresponding remainder for division via #quo:.
 
@@ -602,11 +602,11 @@
     |abs rem negativeDivisor|
 
     aNumber negative ifTrue:[
-        negativeDivisor := true.
-        abs := aNumber negated.
+	negativeDivisor := true.
+	abs := aNumber negated.
     ] ifFalse:[
-        negativeDivisor := false.
-        abs := aNumber.
+	negativeDivisor := false.
+	abs := aNumber.
     ].
 
     "
@@ -614,33 +614,33 @@
      Use a special method for this case ...
     "
     (aNumber class == SmallInteger) ifTrue:[
-        (abs between:1 and:(SmallInteger maxBytes == 8 ifTrue:16r00ffffffffff ifFalse:16r00ffffff)) ifTrue:[
-            rem := (self absFastDivMod:abs) at:2.
-        ] ifFalse:[
-            rem := self absMod:abs asLargeInteger
-        ].
+	(abs between:1 and:(SmallInteger maxBytes == 8 ifTrue:16r00ffffffffff ifFalse:16r00ffffff)) ifTrue:[
+	    rem := (self absFastDivMod:abs) at:2.
+	] ifFalse:[
+	    rem := self absMod:abs asLargeInteger
+	].
     ] ifFalse:[
-        "
-         if the argument is not a largeInteger, coerce
-        "
-        (aNumber class == self class) ifFalse:[
-            ^ self retry:#\\ coercing:aNumber
-        ].
-
-        rem := self absMod:abs.
+	"
+	 if the argument is not a largeInteger, coerce
+	"
+	(aNumber class == self class) ifFalse:[
+	    ^ self retry:#\\ coercing:aNumber
+	].
+
+	rem := self absMod:abs.
     ].
 
     rem = 0 ifFalse:[
-        negativeDivisor ifTrue:[
-            rem := rem setSign:-1
-        ].
-        (self negative ~~ negativeDivisor) ifTrue:[
-            "different sign, so remainder would have been negative.
-             rem has been rounded toward zero, this code will simulate
-             rounding to negative infinity."
-
-            rem := aNumber - rem.
-        ].
+	negativeDivisor ifTrue:[
+	    rem := rem setSign:-1
+	].
+	(self negative ~~ negativeDivisor) ifTrue:[
+	    "different sign, so remainder would have been negative.
+	     rem has been rounded toward zero, this code will simulate
+	     rounding to negative infinity."
+
+	    rem := aNumber - rem.
+	].
     ].
     ^ rem
 
@@ -747,55 +747,73 @@
      special case for SmallInteger minVal
     "
     sign == 1 ifTrue:[
-        sz := digitByteArray size.
+	sz := digitByteArray size.
 %{
-        int idx;
-        unsigned char *bp;
-
-        bp = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
-        idx = __intVal(sz);
-
-        while ((idx > 1) && (bp[idx-1] == 0)) idx--;
-
-        if (idx == sizeof(INT)) {
-#if defined(__LSBFIRST__)
-# if __POINTER_SIZE__ == 8
-            if ( ((unsigned INT *)bp)[0] == 0x4000000000000000L)
+#ifdef __SCHTEAM__
+#else /* not SCHTEAM */
+	int idx;
+	unsigned char *bp;
+
+	bp = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
+	idx = __intVal(sz);
+
+	while ((idx > 1) && (bp[idx-1] == 0)) idx--;
+
+	if (idx == sizeof(INT)) {
+# if defined(__LSBFIRST__)
+#  if __POINTER_SIZE__ == 8
+	    if ( ((unsigned INT *)bp)[0] == 0x4000000000000000L)
+#  else
+	    if ( ((unsigned INT *)bp)[0] == 0x40000000)
+#  endif
 # else
-            if ( ((unsigned INT *)bp)[0] == 0x40000000)
+	    /*
+	     * generic code
+	     */
+	    if ((bp[idx-1] == 0x40)
+	     && (bp[idx-2] == 0)
+	     && (bp[idx-3] == 0)
+	     && (bp[idx-4] == 0)
+#  if __POINTER_SIZE__ == 8
+	     && (bp[idx-5] == 0)
+	     && (bp[idx-6] == 0)
+	     && (bp[idx-7] == 0)
+	     && (bp[idx-8] == 0)
+#  endif
+	    )
 # endif
-#else
-            /*
-             * generic code
-             */
-            if ((bp[idx-1] == 0x40)
-             && (bp[idx-2] == 0)
-             && (bp[idx-3] == 0)
-             && (bp[idx-4] == 0)
-# if __POINTER_SIZE__ == 8
-             && (bp[idx-5] == 0)
-             && (bp[idx-6] == 0)
-             && (bp[idx-7] == 0)
-             && (bp[idx-8] == 0)
-# endif
-            )
+	    {
+		RETURN (__mkSmallInteger(_MIN_INT));
+	    }
+	}
 #endif
-            {
-                RETURN (__mkSmallInteger(_MIN_INT));
-            }
-        }
 %}.
-"/      sz == 4 ifTrue:[
-"/        (digitByteArray at:1) == 0 ifTrue:[
-"/          (digitByteArray at:2) == 0 ifTrue:[
-"/            (digitByteArray at:3) == 0 ifTrue:[
-"/              (digitByteArray at:4) == 16r40 ifTrue:[
-"/                ^ SmallInteger minVal
-"/              ].
-"/            ]
-"/          ]
-"/        ]
-"/      ]
+
+	sz == SmallInteger maxBytes ifTrue:[
+	  (digitByteArray at:1) == 0 ifTrue:[
+	   (digitByteArray at:2) == 0 ifTrue:[
+	    (digitByteArray at:3) == 0 ifTrue:[
+		SmallInteger maxBytes == 8 ifTrue:[
+		  (digitByteArray at:4) == 0 ifTrue:[
+		   (digitByteArray at:5) == 0 ifTrue:[
+		    (digitByteArray at:6) == 0 ifTrue:[
+		     (digitByteArray at:7) == 0 ifTrue:[
+		      (digitByteArray at:8) == 16r40 ifTrue:[
+			^ SmallInteger minVal
+		      ].
+		     ]
+		    ]
+		   ]
+		  ]
+		] ifFalse:[
+		  (digitByteArray at:4) == 16r40 ifTrue:[
+		    ^ SmallInteger minVal
+		  ].
+		]
+	    ]
+	   ]
+	  ]
+	].
     ].
     "/ cg - can share the digits ...
     newNumber := self class digitBytes:digitByteArray sign:(sign negated).
@@ -809,7 +827,7 @@
      The results sign is negative if the receiver has a sign
      different from the args sign.
      The following is always true:
-        (receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
+	(receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
     "
 
     |otherSign quo abs "{ Class: SmallInteger }" |
@@ -821,26 +839,26 @@
      Use a special method for this case ...
     "
     (aNumber class == SmallInteger) ifTrue:[
-        abs := aNumber.
-        abs := abs abs.
-        (abs between:1 and:16r00ffffff) ifTrue:[
-            quo := (self absFastDivMod:abs) at:1.
-            (sign == otherSign) ifTrue:[^ quo].
-            ^ quo setSign:-1
-        ]
+	abs := aNumber.
+	abs := abs abs.
+	(abs between:1 and:16r00ffffff) ifTrue:[
+	    quo := (self absFastDivMod:abs) at:1.
+	    (sign == otherSign) ifTrue:[^ quo].
+	    ^ quo setSign:-1
+	]
     ].
 
     "
      if the argument is not a largeInteger, coerce
     "
     (aNumber class == self class) ifFalse:[
-        ^ self retry:#quo: coercing:aNumber
+	^ self retry:#quo: coercing:aNumber
     ].
 
     sign < 0 ifTrue:[
-        (sign == otherSign) ifTrue:[^ (self absDivMod:aNumber negated) at:1].
+	(sign == otherSign) ifTrue:[^ (self absDivMod:aNumber negated) at:1].
     ] ifFalse:[
-        (sign == otherSign) ifTrue:[^ (self absDivMod:aNumber) at:1].
+	(sign == otherSign) ifTrue:[^ (self absDivMod:aNumber) at:1].
     ].
     ^ ((self absDivMod:aNumber) at:1) setSign:-1
 
@@ -874,7 +892,7 @@
     "return the remainder of division of the receiver by the argument, aNumber.
      The returned remainder has the same sign as the receiver.
      The following is always true:
-        (receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
+	(receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
     "
 
     |rem abs "{ Class: SmallInteger }" |
@@ -884,26 +902,26 @@
      Use special code for this case ...
     "
     (aNumber class == SmallInteger) ifTrue:[
-        abs := aNumber.
-        abs := abs abs.
-        (abs between:1 and:16r00ffffff) ifTrue:[
-            rem := (self absFastDivMod:abs) at:2.
-        ] ifFalse:[
-            rem := self absMod:abs asLargeInteger
-        ].
+	abs := aNumber.
+	abs := abs abs.
+	(abs between:1 and:16r00ffffff) ifTrue:[
+	    rem := (self absFastDivMod:abs) at:2.
+	] ifFalse:[
+	    rem := self absMod:abs asLargeInteger
+	].
     ] ifFalse:[
-        "
-         if the argument is not a largeInteger, coerce
-        "
-        (aNumber class == self class) ifFalse:[
-            ^ self retry:#rem coercing:aNumber
-        ].
-
-        rem := self absMod:aNumber
+	"
+	 if the argument is not a largeInteger, coerce
+	"
+	(aNumber class == self class) ifFalse:[
+	    ^ self retry:#rem coercing:aNumber
+	].
+
+	rem := self absMod:aNumber
     ].
 
     sign < 0 ifTrue:[
-        ^ rem setSign:-1
+	^ rem setSign:-1
     ].
     ^ rem
 
@@ -1327,23 +1345,23 @@
     |myDigitLength newDigitLength newDigitBytes byteIndexOfBitToSet|
 
     index <= 0 ifTrue:[
-        ^ SubscriptOutOfBoundsSignal
-                raiseRequestWith:index
-                errorString:'index out of bounds'
+	^ SubscriptOutOfBoundsSignal
+		raiseRequestWith:index
+		errorString:'index out of bounds'
     ].
 
     myDigitLength := digitByteArray size.
     byteIndexOfBitToSet := ((index-1)//8)+1.
     byteIndexOfBitToSet > myDigitLength ifTrue:[
-        newDigitLength := myDigitLength max:byteIndexOfBitToSet.
-        newDigitBytes := ByteArray new:newDigitLength.
-        newDigitBytes replaceFrom:1 to:myDigitLength with:digitByteArray startingAt:1.
+	newDigitLength := myDigitLength max:byteIndexOfBitToSet.
+	newDigitBytes := ByteArray new:newDigitLength.
+	newDigitBytes replaceFrom:1 to:myDigitLength with:digitByteArray startingAt:1.
     ] ifFalse:[
-        newDigitBytes := digitByteArray copy
+	newDigitBytes := digitByteArray copy
     ].
     newDigitBytes
-        at:byteIndexOfBitToSet
-        put:((newDigitBytes at:byteIndexOfBitToSet) setBit:(((index-1)\\8)+1)).
+	at:byteIndexOfBitToSet
+	put:((newDigitBytes at:byteIndexOfBitToSet) setBit:(((index-1)\\8)+1)).
     ^ self class digitBytes:newDigitBytes sign:sign
 
     "
@@ -1599,10 +1617,10 @@
 #endif
 %}.
     sign >= 0 ifTrue:[
-        index > digitByteArray size ifTrue:[
-            ^ 0
-        ].
-        ^ digitByteArray at:index.
+	index > digitByteArray size ifTrue:[
+	    ^ 0
+	].
+	^ digitByteArray at:index.
     ].
 
     "/ negative int - do 2's complement here
@@ -1611,7 +1629,7 @@
     t setSign:1.
     digits := t digitBytes.
     index > digits size ifTrue:[
-        ^ 16rFF
+	^ 16rFF
     ].
     ^ digits at:index.
 
@@ -2360,38 +2378,38 @@
 
     num := anInteger abs.
     (num > 16r3FFFFF) ifTrue:[
-        "if num is too big (so that multiplying by a byte could create a Large)"
-
-        ^ anInteger retry:#* coercing:self
+	"if num is too big (so that multiplying by a byte could create a Large)"
+
+	^ anInteger retry:#* coercing:self
     ].
 
     len := digitByteArray size.
 
     val := num.
     val <= 16rFF ifTrue:[
-        lResult := len + 1.
+	lResult := len + 1.
     ] ifFalse:[
-        val <= 16rFFFF ifTrue:[
-            lResult := len + 2
-        ] ifFalse:[
-            val <= 16rFFFFFF ifTrue:[
-                lResult := len + 4.
-            ] ifFalse:[
-                lResult := len + 6.
-            ]
-        ]
+	val <= 16rFFFF ifTrue:[
+	    lResult := len + 2
+	] ifFalse:[
+	    val <= 16rFFFFFF ifTrue:[
+		lResult := len + 4.
+	    ] ifFalse:[
+		lResult := len + 6.
+	    ]
+	]
     ].
     resultDigitByteArray := ByteArray uninitializedNew:lResult.
     result := self class basicNew setDigits:resultDigitByteArray.
 
     anInteger < 0 ifTrue:[
-        sign > 0 ifTrue:[
-            result setSign:-1
-        ].
+	sign > 0 ifTrue:[
+	    result setSign:-1
+	].
     ] ifFalse:[
-        sign < 0 ifTrue:[
-            result setSign:sign
-        ]
+	sign < 0 ifTrue:[
+	    result setSign:sign
+	]
     ].
 
     ok := false.
@@ -2401,156 +2419,156 @@
     if (__isSmallInteger(len)
      && __isByteArray(__digitByteArray)
      && __isByteArray(resultDigitByteArray)) {
-        INT _l = __intVal(len);
-        INT _v = __intVal(val);
-        unsigned INT _carry = 0;
-        unsigned INT _prod;
-        unsigned char *digitP = __ByteArrayInstPtr(__digitByteArray)->ba_element;
-        unsigned char *resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
-
-        /*
-         * skipping zeros does not help much (a few percent) on
-         * a P5 or other CPUS with a fast multiplier.
-         * It may make more of a difference on CPUs with slower 0-multiply.
-         */
-        while ((_l >= sizeof(INT)) && (((unsigned INT *)digitP)[0] == 0)) {
-            ((unsigned INT *)resultP)[0] = 0;
-            digitP += sizeof(INT);
-            resultP += sizeof(INT);
-            _l -= sizeof(INT);
-        }
+	INT _l = __intVal(len);
+	INT _v = __intVal(val);
+	unsigned INT _carry = 0;
+	unsigned INT _prod;
+	unsigned char *digitP = __ByteArrayInstPtr(__digitByteArray)->ba_element;
+	unsigned char *resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
+
+	/*
+	 * skipping zeros does not help much (a few percent) on
+	 * a P5 or other CPUS with a fast multiplier.
+	 * It may make more of a difference on CPUs with slower 0-multiply.
+	 */
+	while ((_l >= sizeof(INT)) && (((unsigned INT *)digitP)[0] == 0)) {
+	    ((unsigned INT *)resultP)[0] = 0;
+	    digitP += sizeof(INT);
+	    resultP += sizeof(INT);
+	    _l -= sizeof(INT);
+	}
 
 #if defined(__LSBFIRST__)
 # if defined (__GNUC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
-        /*
-         * can do it long-word-wise;
-         * 32*32 -> 64 multiplication
-         */
-        while (_l > 3) {
-            unsigned __pHi, __pLow;
-            unsigned __digit;
-
-            /*
-             * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
-             * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
-             */
-            __digit = ((unsigned long *)digitP)[0];
-            asm ("mull %3               \n\
-                  addl %4,%%eax         \n\
-                  adcl $0,%%edx"
-                    : "=a"  (__pLow),
-                      "=d"  (__pHi)
-                    : "0"   (__digit),
-                      "1"   ((unsigned long)(_v)),
-                      "rm"  ((unsigned long)(_carry)) );
-
-            ((unsigned long *)resultP)[0] = __pLow;
-            _carry = __pHi;
-            digitP += 4;
-            resultP += 4;
-            _l -= 4;
-        }
+	/*
+	 * can do it long-word-wise;
+	 * 32*32 -> 64 multiplication
+	 */
+	while (_l > 3) {
+	    unsigned __pHi, __pLow;
+	    unsigned __digit;
+
+	    /*
+	     * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
+	     * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
+	     */
+	    __digit = ((unsigned long *)digitP)[0];
+	    asm ("mull %3               \n\
+		  addl %4,%%eax         \n\
+		  adcl $0,%%edx"
+		    : "=a"  (__pLow),
+		      "=d"  (__pHi)
+		    : "0"   (__digit),
+		      "1"   ((unsigned long)(_v)),
+		      "rm"  ((unsigned long)(_carry)) );
+
+	    ((unsigned long *)resultP)[0] = __pLow;
+	    _carry = __pHi;
+	    digitP += 4;
+	    resultP += 4;
+	    _l -= 4;
+	}
 # else /* not GNU-i386 */
 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
-        /*
-         * can do it long-word-wise;
-         * 32*32 -> 64 multiplication
-         */
-        while (_l > 3) {
-            unsigned __pLow;
-            unsigned digit;
-
-            /*
-             * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
-             * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
-             */
+	/*
+	 * can do it long-word-wise;
+	 * 32*32 -> 64 multiplication
+	 */
+	while (_l > 3) {
+	    unsigned __pLow;
+	    unsigned digit;
+
+	    /*
+	     * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
+	     * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
+	     */
 /*
-            digit = ((unsigned long *)digitP)[0];
-            edx::eax = (digit * _v);
-            edx::eax += _carry;
-            ((unsigned long *)resultP)[0] = eax; -- pLow
-            _carry = edx; -- pHigh
-            digitP += 4;
-            resultP += 4;
+	    digit = ((unsigned long *)digitP)[0];
+	    edx::eax = (digit * _v);
+	    edx::eax += _carry;
+	    ((unsigned long *)resultP)[0] = eax; -- pLow
+	    _carry = edx; -- pHigh
+	    digitP += 4;
+	    resultP += 4;
 */
-            digit = ((unsigned long *)digitP)[0];
-            asm {
-                mov   eax, digit
-                mov   edx, _v
-                mul   edx
-                add   eax, _carry
-                adc   edx, 0
-                mov   __pLow, eax
-                mov   _carry, edx
-            }
-
-            ((unsigned long *)resultP)[0] = __pLow;
-            digitP += 4;
-            resultP += 4;
-            _l -= 4;
-        }
+	    digit = ((unsigned long *)digitP)[0];
+	    asm {
+		mov   eax, digit
+		mov   edx, _v
+		mul   edx
+		add   eax, _carry
+		adc   edx, 0
+		mov   __pLow, eax
+		mov   _carry, edx
+	    }
+
+	    ((unsigned long *)resultP)[0] = __pLow;
+	    digitP += 4;
+	    resultP += 4;
+	    _l -= 4;
+	}
 #  else /* not WIN32-i386 */
 #   if defined(INT64)
-        if (_v <= 0xFFFFFFFFL) {
-            /*
-             * have a 64bit int type ... good
-             */
-            UINT64 _prod64;
-
-            /* have 64bit ints; can do it int-wise
-             *
-             * max: 0xFFFFFFFF * 0xFFFFFFFF -> 0xFFFFFFFE.0001
-             * + maxCarry (0xFFFFFFFF)  -> 0xFFFFFFFF.0000
-             */
-            while (_l > 3) {
-                unsigned __t;
-
-                __t = ((unsigned *)digitP)[0];
-                digitP += 4;
-                _prod64 = (INT64)_v;
-                _prod64 *= __t;
-                _prod64 += _carry;
-                ((unsigned *)resultP)[0] = _prod64 /* & 0xFFFFFFFFL */;
-                _carry = _prod64 >> 32;
-                resultP += 4;
-                _l -= 4;
-            }
-            if (_l > 1) {
-                unsigned short __t;
-
-                __t = ((unsigned short *)digitP)[0];
-                digitP += 2;
-                _prod64 = (INT64)_v;
-                _prod64 *= __t;
-                _prod64 += _carry;
-                ((unsigned short *)resultP)[0] = _prod64 /* & 0xFFFF */;
-                _carry = _prod64 >> 16;
-                resultP += 2;
-                _l -= 2;
-            }
-            if (_l > 0) {
-                _prod64 = *digitP++ * _v + _carry;
-                *resultP++ = _prod64 /* & 0xFF */;
-                _carry = _prod64 >> 8;
-                _l--;
-            }
-        }
+	if (_v <= 0xFFFFFFFFL) {
+	    /*
+	     * have a 64bit int type ... good
+	     */
+	    UINT64 _prod64;
+
+	    /* have 64bit ints; can do it int-wise
+	     *
+	     * max: 0xFFFFFFFF * 0xFFFFFFFF -> 0xFFFFFFFE.0001
+	     * + maxCarry (0xFFFFFFFF)  -> 0xFFFFFFFF.0000
+	     */
+	    while (_l > 3) {
+		unsigned __t;
+
+		__t = ((unsigned *)digitP)[0];
+		digitP += 4;
+		_prod64 = (INT64)_v;
+		_prod64 *= __t;
+		_prod64 += _carry;
+		((unsigned *)resultP)[0] = _prod64 /* & 0xFFFFFFFFL */;
+		_carry = _prod64 >> 32;
+		resultP += 4;
+		_l -= 4;
+	    }
+	    if (_l > 1) {
+		unsigned short __t;
+
+		__t = ((unsigned short *)digitP)[0];
+		digitP += 2;
+		_prod64 = (INT64)_v;
+		_prod64 *= __t;
+		_prod64 += _carry;
+		((unsigned short *)resultP)[0] = _prod64 /* & 0xFFFF */;
+		_carry = _prod64 >> 16;
+		resultP += 2;
+		_l -= 2;
+	    }
+	    if (_l > 0) {
+		_prod64 = *digitP++ * _v + _carry;
+		*resultP++ = _prod64 /* & 0xFF */;
+		_carry = _prod64 >> 8;
+		_l--;
+	    }
+	}
 #   else /* no INT64 type */
-        if (_v <= 0xFFFF) {
-            /* can do it short-wise
-             *
-             * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
-             * + maxCarry (0xFFFF)  -> 0xFFFF.0000
-             */
-            while (_l > 1) {
-                _prod = ((unsigned short *)digitP)[0] * _v + _carry;
-                ((unsigned short *)resultP)[0] = _prod /* & 0xFFFF */;
-                _carry = _prod >> 16;
-                digitP += 2;
-                resultP += 2;
-                _l -= 2;
-            }
-        }
+	if (_v <= 0xFFFF) {
+	    /* can do it short-wise
+	     *
+	     * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
+	     * + maxCarry (0xFFFF)  -> 0xFFFF.0000
+	     */
+	    while (_l > 1) {
+		_prod = ((unsigned short *)digitP)[0] * _v + _carry;
+		((unsigned short *)resultP)[0] = _prod /* & 0xFFFF */;
+		_carry = _prod >> 16;
+		digitP += 2;
+		resultP += 2;
+		_l -= 2;
+	    }
+	}
 #   endif /* no INT64 */
 #  endif /* not WIN32-i386 */
 # endif /* not GNU-i386 */
@@ -2561,80 +2579,80 @@
    /* no, STORE_WORD_WISE makes it slower */
 # endif
 
-        if (_v <= 0xFFFF) {
-            /* can do it short-wise
-             *
-             * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
-             * + maxCarry (0xFFFF)  -> 0xFFFF.0000
-             */
-            while (_l > 1) {
-                unsigned int t;
+	if (_v <= 0xFFFF) {
+	    /* can do it short-wise
+	     *
+	     * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
+	     * + maxCarry (0xFFFF)  -> 0xFFFF.0000
+	     */
+	    while (_l > 1) {
+		unsigned int t;
 
 #if defined(LOAD_WORD_WISE)
-                /* better fetch short-wise */
-                t = ((unsigned short *)digitP)[0];
-                digitP += 2;
-                t = ((t >> 8) | (t << 8)) & 0xFFFF;
+		/* better fetch short-wise */
+		t = ((unsigned short *)digitP)[0];
+		digitP += 2;
+		t = ((t >> 8) | (t << 8)) & 0xFFFF;
 #else
-                t = (digitP[1]<<8) + digitP[0];
-                digitP += 2;
+		t = (digitP[1]<<8) + digitP[0];
+		digitP += 2;
 #endif
-                _prod = t * _v + _carry;
-                _carry = _prod >> 16;
+		_prod = t * _v + _carry;
+		_carry = _prod >> 16;
 #if defined(STORE_WORD_WISE)
-                /* better store short-wise */
-                _prod = ((_prod >> 8) | (_prod << 8)) & 0xFFFF;
-                ((unsigned short *)resultP)[0] = _prod;
+		/* better store short-wise */
+		_prod = ((_prod >> 8) | (_prod << 8)) & 0xFFFF;
+		((unsigned short *)resultP)[0] = _prod;
 #else
-                resultP[0] = _prod /* & 0xFF */;
-                resultP[1] = (_prod>>8) /* & 0xFF */;
+		resultP[0] = _prod /* & 0xFF */;
+		resultP[1] = (_prod>>8) /* & 0xFF */;
 #endif
-                resultP += 2;
-                _l -= 2;
-            }
-        }
+		resultP += 2;
+		_l -= 2;
+	    }
+	}
 
 #endif /* LSB_FIRST */
 
-        /*
-         * rest is done byte-wise
-         */
-        while (_l > 0) {
-            _prod = *digitP++ * _v + _carry;
-            *resultP++ = _prod /* & 0xFF */;
-            _carry = _prod >> 8;
-            _l--;
-        }
-
-        _l = __intVal(lResult) - __intVal(len);
-
-        /*
-         * remaining carry
-         */
-        while (_carry) {
-            *resultP++ = _carry /* & 0xFF */;
-            _carry >>= 8;
-            _l--;
-        }
-
-        /*
-         * remaining zeros
-         */
-        while (_l--) {
-            *resultP++ = 0;
-        }
-
-        /*
-         * need compress ?
-         */
-        if (resultP[-1]) {
-            /*
-             * no
-             */
-            RETURN(result);
-        }
-
-        ok = true;
+	/*
+	 * rest is done byte-wise
+	 */
+	while (_l > 0) {
+	    _prod = *digitP++ * _v + _carry;
+	    *resultP++ = _prod /* & 0xFF */;
+	    _carry = _prod >> 8;
+	    _l--;
+	}
+
+	_l = __intVal(lResult) - __intVal(len);
+
+	/*
+	 * remaining carry
+	 */
+	while (_carry) {
+	    *resultP++ = _carry /* & 0xFF */;
+	    _carry >>= 8;
+	    _l--;
+	}
+
+	/*
+	 * remaining zeros
+	 */
+	while (_l--) {
+	    *resultP++ = 0;
+	}
+
+	/*
+	 * need compress ?
+	 */
+	if (resultP[-1]) {
+	    /*
+	     * no
+	     */
+	    RETURN(result);
+	}
+
+	ok = true;
     }
 %}.
     "
@@ -2642,21 +2660,21 @@
      (could make it a primitive-failure as well)
     "
     ok ifFalse:[
-        carry := 0.
-        1 to:len do:[:i |
-            prod := (digitByteArray basicAt:i) * val + carry.
-            resultDigitByteArray basicAt:i put:(prod bitAnd:16rFF).
-            carry := prod bitShift:-8.
-        ].
-        [carry ~~ 0] whileTrue:[
-            len := len + 1.
-            resultDigitByteArray basicAt:len put:(carry bitAnd:16rFF).
-            carry := carry bitShift:-8
-        ].
-        [len < lResult] whileTrue:[
-            len := len + 1.
-            resultDigitByteArray basicAt:len put:0
-        ]
+	carry := 0.
+	1 to:len do:[:i |
+	    prod := (digitByteArray basicAt:i) * val + carry.
+	    resultDigitByteArray basicAt:i put:(prod bitAnd:16rFF).
+	    carry := prod bitShift:-8.
+	].
+	[carry ~~ 0] whileTrue:[
+	    len := len + 1.
+	    resultDigitByteArray basicAt:len put:(carry bitAnd:16rFF).
+	    carry := carry bitShift:-8
+	].
+	[len < lResult] whileTrue:[
+	    len := len + 1.
+	    resultDigitByteArray basicAt:len put:0
+	]
     ].
     ^ result compressed
 !
@@ -3061,7 +3079,7 @@
 
     ((aSmallInteger < (SmallInteger minVal + 255))
     or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
-        ^ self absMinus:(self class value:aSmallInteger) sign:newSign.
+	^ self absMinus:(self class value:aSmallInteger) sign:newSign.
     ].
 
     len := digitByteArray size.
@@ -3075,123 +3093,123 @@
 %{
     if (__isByteArray(__INST(digitByteArray))
      && __isByteArray(resultDigitByteArray)) {
-        unsigned INT __borrow = __intVal(borrow);
-        INT __diff;
-        int __index = 1;
-        int __len = __intVal(len);
-        unsigned char *__digitP = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
-        unsigned char *__resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
-        int __len3;
+	unsigned INT __borrow = __intVal(borrow);
+	INT __diff;
+	int __index = 1;
+	int __len = __intVal(len);
+	unsigned char *__digitP = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
+	unsigned char *__resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
+	int __len3;
 
 #if defined(__LSBFIRST__)
 # if (__POINTER_SIZE__ == 8)
-        /*
-         * subtract int-wise
-         */
-        __len3 = __len - 3;
-        while (__index < __len3) {
-            /* do not make this into one expression - ask cg why */
-            __diff = ((unsigned int *)(__digitP + __index-1))[0];
-            __diff -= (__borrow & 0xFFFFFFFFL);
-            __borrow >>= 32;
-            if (__diff < 0) {
-                /* __diff += 0x100000000; */
-                __borrow++;
-            }
-            ((unsigned int *)(__resultP+__index-1))[0] = __diff;
-            __index += 4;
-        }
+	/*
+	 * subtract int-wise
+	 */
+	__len3 = __len - 3;
+	while (__index < __len3) {
+	    /* do not make this into one expression - ask cg why */
+	    __diff = ((unsigned int *)(__digitP + __index-1))[0];
+	    __diff -= (__borrow & 0xFFFFFFFFL);
+	    __borrow >>= 32;
+	    if (__diff < 0) {
+		/* __diff += 0x100000000; */
+		__borrow++;
+	    }
+	    ((unsigned int *)(__resultP+__index-1))[0] = __diff;
+	    __index += 4;
+	}
 # endif
-        /*
-         * subtract short-wise
-         */
-        while (__index < __len) {
-            /* do not make this into one expression - ask cg why */
-            __diff = ((unsigned short *)(__digitP+__index-1))[0];
-            __diff -= (__borrow & 0xFFFF);
-            __borrow >>= 16;
-            if (__diff < 0) {
-                /* __diff += 0x10000; */
-                __borrow++;
-            } else {
-                if (__borrow == 0) {
-                    ((unsigned short *)(__resultP+__index-1))[0] = __diff;
-                    __index += 2;
-
-                    /* nothing more to subtract .. */
-                    while (__index < __len) {
-                        ((unsigned short *)(__resultP+__index-1))[0] = ((unsigned short *)(__digitP+__index-1))[0];
-                        __index += 2;
-                    }
-                    if (__index <= __len) {
-                        __resultP[__index-1] = __digitP[__index-1];
-                    }
-                    break;
-                }
-            }
-            ((unsigned short *)(__resultP+__index-1))[0] = __diff;
-            __index += 2;
-        }
+	/*
+	 * subtract short-wise
+	 */
+	while (__index < __len) {
+	    /* do not make this into one expression - ask cg why */
+	    __diff = ((unsigned short *)(__digitP+__index-1))[0];
+	    __diff -= (__borrow & 0xFFFF);
+	    __borrow >>= 16;
+	    if (__diff < 0) {
+		/* __diff += 0x10000; */
+		__borrow++;
+	    } else {
+		if (__borrow == 0) {
+		    ((unsigned short *)(__resultP+__index-1))[0] = __diff;
+		    __index += 2;
+
+		    /* nothing more to subtract .. */
+		    while (__index < __len) {
+			((unsigned short *)(__resultP+__index-1))[0] = ((unsigned short *)(__digitP+__index-1))[0];
+			__index += 2;
+		    }
+		    if (__index <= __len) {
+			__resultP[__index-1] = __digitP[__index-1];
+		    }
+		    break;
+		}
+	    }
+	    ((unsigned short *)(__resultP+__index-1))[0] = __diff;
+	    __index += 2;
+	}
 #endif
-        /*
-         * subtract byte-wise
-         */
-        while (__index <= __len) {
-            __diff = __digitP[__index-1];
-            __diff -= (__borrow & 0xFF);
-            __borrow >>= 8;
-            if (__diff < 0) {
-                /* __diff += 0x100; */
-                __borrow++;
-            } else {
-                if (__borrow == 0) {
-                    __resultP[__index-1] = __diff;
-                    __index++;
-
-                    /* nothing more to subtract .. */
-                    while (__index <= __len) {
-                        __resultP[__index-1] = __digitP[__index-1];
-                        __index++;
-                    }
-                    break;
-                }
-            }
-            __resultP[__index-1] = __diff;
-            __index++;
-        }
-        lastDigit = __mkSmallInteger( __resultP[__index-1-1] );
-        ok = true;
+	/*
+	 * subtract byte-wise
+	 */
+	while (__index <= __len) {
+	    __diff = __digitP[__index-1];
+	    __diff -= (__borrow & 0xFF);
+	    __borrow >>= 8;
+	    if (__diff < 0) {
+		/* __diff += 0x100; */
+		__borrow++;
+	    } else {
+		if (__borrow == 0) {
+		    __resultP[__index-1] = __diff;
+		    __index++;
+
+		    /* nothing more to subtract .. */
+		    while (__index <= __len) {
+			__resultP[__index-1] = __digitP[__index-1];
+			__index++;
+		    }
+		    break;
+		}
+	    }
+	    __resultP[__index-1] = __diff;
+	    __index++;
+	}
+	lastDigit = __mkSmallInteger( __resultP[__index-1-1] );
+	ok = true;
     }
 %}.
 
     ok == true ifFalse:[        "/ cannot happen
-        index := 1.
-        [borrow ~~ 0] whileTrue:[
-            (index <= len) ifTrue:[
-                diff := (digitByteArray basicAt:index) - (borrow bitAnd:16rFF).
-                borrow := borrow bitShift:-8.
-                diff < 0 ifTrue:[
-                    diff := diff + 256.
-                    borrow := borrow + 1.
-                ]
-            ] ifFalse:[
-                diff := borrow bitAnd:255.
-                borrow := borrow bitShift:-8.
-            ].
-            resultDigitByteArray basicAt:index put:(lastDigit := diff).
-            index := index + 1
-        ].
-        [index <= len] whileTrue:[
-            resultDigitByteArray basicAt:index put:(lastDigit := digitByteArray basicAt:index).
-            index := index + 1
-        ].
-        (index <= rsltLen) ifTrue:[
-            lastDigit := 0.
-        ]
+	index := 1.
+	[borrow ~~ 0] whileTrue:[
+	    (index <= len) ifTrue:[
+		diff := (digitByteArray basicAt:index) - (borrow bitAnd:16rFF).
+		borrow := borrow bitShift:-8.
+		diff < 0 ifTrue:[
+		    diff := diff + 256.
+		    borrow := borrow + 1.
+		]
+	    ] ifFalse:[
+		diff := borrow bitAnd:255.
+		borrow := borrow bitShift:-8.
+	    ].
+	    resultDigitByteArray basicAt:index put:(lastDigit := diff).
+	    index := index + 1
+	].
+	[index <= len] whileTrue:[
+	    resultDigitByteArray basicAt:index put:(lastDigit := digitByteArray basicAt:index).
+	    index := index + 1
+	].
+	(index <= rsltLen) ifTrue:[
+	    lastDigit := 0.
+	]
     ].
 
     (lastDigit == 0 or:[rsltLen <= SmallInteger maxBytes]) ifTrue:[
-        ^ result compressed.
+	^ result compressed.
     ].
     ^ result
 
@@ -3226,7 +3244,7 @@
 
     ((aSmallInteger < (SmallInteger minVal + 255))
     or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
-        ^ self absPlus:(self class value:aSmallInteger) sign:newSign.
+	^ self absPlus:(self class value:aSmallInteger) sign:newSign.
     ].
 
     len := rsltLen := digitByteArray size.
@@ -3235,18 +3253,18 @@
     "/ if it is 255 (since the other number is definitely smaller)
     "/
     (digitByteArray at:len) == 16rFF ifTrue:[
-        rsltLen := len + 1.
+	rsltLen := len + 1.
     ] ifFalse:[
-        "/ or the argument has something in the high byte ..
+	"/ or the argument has something in the high byte ..
 %{
 #if __POINTER_SIZE__ == 8
-        if (__intVal(aSmallInteger) & 0xFF00000000000000L) {
-            rsltLen = __mkSmallInteger(__intVal(len) + 1);
-        }
+	if (__intVal(aSmallInteger) & 0xFF00000000000000L) {
+	    rsltLen = __mkSmallInteger(__intVal(len) + 1);
+	}
 #else
-        if (__intVal(aSmallInteger) & 0xFF000000) {
-            rsltLen = __mkSmallInteger(__intVal(len) + 1);
-        }
+	if (__intVal(aSmallInteger) & 0xFF000000) {
+	    rsltLen = __mkSmallInteger(__intVal(len) + 1);
+	}
 #endif
 %}
     ].
@@ -3258,307 +3276,307 @@
     if (__isByteArray(__INST(digitByteArray))
      && __isByteArray(resultDigitByteArray)
      && __isSmallInteger(aSmallInteger)) {
-        /* carry is NOT unsigned (see negation below) */
-        INT __carry = __intVal(aSmallInteger);
-        int __index = 1;
-        int __len = __intVal(len);
-        unsigned char *__src = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
-        unsigned char *__dst = (unsigned char *)(__ByteArrayInstPtr(resultDigitByteArray)->ba_element);
-        INT __ptrDelta = __dst - __src;
-        unsigned char *__srcLast = __src + __len - 1;
-        int __rsltLen = __intVal(rsltLen);
-
-        if (__carry < 0) {
-            __carry = -__carry;
-        }
+	/* carry is NOT unsigned (see negation below) */
+	INT __carry = __intVal(aSmallInteger);
+	int __index = 1;
+	int __len = __intVal(len);
+	unsigned char *__src = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
+	unsigned char *__dst = (unsigned char *)(__ByteArrayInstPtr(resultDigitByteArray)->ba_element);
+	INT __ptrDelta = __dst - __src;
+	unsigned char *__srcLast = __src + __len - 1;
+	int __rsltLen = __intVal(rsltLen);
+
+	if (__carry < 0) {
+	    __carry = -__carry;
+	}
 
 #if defined(__LSBFIRST__)
 # if defined(__i386__) && defined(__GNUC__) && (__POINTER_SIZE__ == 4)
 #  if 0 /* NOTICE - the code below is 20% slower ... - why */
-        /*
-         * add long-wise
-         */
-        asm("  jecxz nothingToDo                                      \n\
-               movl  %%eax, %%esi      /* __src input */              \n\
-               movl  %%ebx, %%edi      /* __dst input */              \n\
-                                                                      \n\
-               /* the first 4-byte int */                             \n\
-               lodsl                   /* fetch */                    \n\
-               addl  %%edx, %%eax      /* add */                      \n\
-               stosl                   /* store */                    \n\
-               leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
-               jecxz doneLoop          /* any more ? */               \n\
-               /* remaining 4-byte ints */                            \n\
-               jmp   addLoop                                          \n\
-                                                                      \n\
-               .align 8                                               \n\
-             addLoop:                                                 \n\
-               movl  0(%%esi), %%ebx   /* fetch  */                   \n\
-               jnc   copyLoop2                                        \n\
-               movl  $0, %%eax                                        \n\
-               leal  4(%%esi), %%esi                                  \n\
-               adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
-               leal  8(%%edi), %%edi                                  \n\
-               movl  %%eax, -8(%%edi)  /* store */                    \n\
-               leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
-               jecxz doneLoop          /* any more ? */               \n\
-                                                                      \n\
-               movl  0(%%esi), %%ebx   /* fetch  */                   \n\
-               movl  $0, %%eax                                        \n\
-               leal  4(%%esi), %%esi                                  \
-               adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
-               movl  %%eax, -4(%%edi)  /* store */                    \n\
-                                                                      \n\
-               loop  addLoop                                          \n\
-               jmp   doneLoop                                         \n\
-                                                                      \n\
-               .align 8                                               \n\
-             copyLoop:                                                \n\
-               movl  0(%%esi), %%ebx                                  \n\
-             copyLoop2:                                               \n\
-               add   $4, %%esi                                        \n\
-               add   $4, %%edi                                        \n\
-               movl  %%ebx, -4(%%edi)                                 \n\
-               loop  copyLoop                                         \n\
-                                                                      \n\
-             doneLoop:                                                \n\
-               movl  $0, %%edx         /* do not clobber carry (xorl clears it) */   \n\
-               adcl  $0, %%edx                                        \n\
-               movl  %%esi, %%eax      /* __src output */             \n\
-             nothingToDo:                                             \n\
-            " : "=d"  ((unsigned long)(__carry)),
-                "=a"  (__src)
-              : "1"   (__src),
-                "b"   (__dst),
-                "c"   (__len / 4),
-                "0"   (__carry)
-              : "esi", "edi");
+	/*
+	 * add long-wise
+	 */
+	asm("  jecxz nothingToDo                                      \n\
+	       movl  %%eax, %%esi      /* __src input */              \n\
+	       movl  %%ebx, %%edi      /* __dst input */              \n\
+								      \n\
+	       /* the first 4-byte int */                             \n\
+	       lodsl                   /* fetch */                    \n\
+	       addl  %%edx, %%eax      /* add */                      \n\
+	       stosl                   /* store */                    \n\
+	       leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
+	       jecxz doneLoop          /* any more ? */               \n\
+	       /* remaining 4-byte ints */                            \n\
+	       jmp   addLoop                                          \n\
+								      \n\
+	       .align 8                                               \n\
+	     addLoop:                                                 \n\
+	       movl  0(%%esi), %%ebx   /* fetch  */                   \n\
+	       jnc   copyLoop2                                        \n\
+	       movl  $0, %%eax                                        \n\
+	       leal  4(%%esi), %%esi                                  \n\
+	       adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
+	       leal  8(%%edi), %%edi                                  \n\
+	       movl  %%eax, -8(%%edi)  /* store */                    \n\
+	       leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
+	       jecxz doneLoop          /* any more ? */               \n\
+								      \n\
+	       movl  0(%%esi), %%ebx   /* fetch  */                   \n\
+	       movl  $0, %%eax                                        \n\
+	       leal  4(%%esi), %%esi                                  \
+	       adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
+	       movl  %%eax, -4(%%edi)  /* store */                    \n\
+								      \n\
+	       loop  addLoop                                          \n\
+	       jmp   doneLoop                                         \n\
+								      \n\
+	       .align 8                                               \n\
+	     copyLoop:                                                \n\
+	       movl  0(%%esi), %%ebx                                  \n\
+	     copyLoop2:                                               \n\
+	       add   $4, %%esi                                        \n\
+	       add   $4, %%edi                                        \n\
+	       movl  %%ebx, -4(%%edi)                                 \n\
+	       loop  copyLoop                                         \n\
+								      \n\
+	     doneLoop:                                                \n\
+	       movl  $0, %%edx         /* do not clobber carry (xorl clears it) */   \n\
+	       adcl  $0, %%edx                                        \n\
+	       movl  %%esi, %%eax      /* __src output */             \n\
+	     nothingToDo:                                             \n\
+	    " : "=d"  ((unsigned long)(__carry)),
+		"=a"  (__src)
+	      : "1"   (__src),
+		"b"   (__dst),
+		"c"   (__len / 4),
+		"0"   (__carry)
+	      : "esi", "edi");
 
 #  else
-        {
-            unsigned char *__srcLastX;
-
-            __srcLastX = __srcLast - 3 - 4;
-            while (__src <= __srcLastX) {
-                unsigned int __sum, __sum2;
-                unsigned __digit1, __digit2;
-
-                __digit1 = ((unsigned *)__src)[0];
-                __digit2 = ((unsigned *)__src)[1];
-                asm ("addl %%edx,%%ecx          \n\
-                      adcl $0, %%eax            \n\
-                      movl $0, %%edx            \n\
-                      adcl $0, %%edx"
-                        : "=d"  ((unsigned long)(__carry)),
-                          "=c"  ((unsigned long)(__sum)),
-                          "=a"  ((unsigned long)(__sum2))
-                        : "0"   ((unsigned long)(__carry)),
-                          "1"   (__digit1),
-                          "2"   (__digit2));
-
-                ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
-                ((unsigned int *)(__src + __ptrDelta))[1] = __sum2;
-
-                __src += 8;
-
-                if (__carry == 0) {
-                    while (__src <= __srcLastX) {
-                        /* copy over words */
-                        ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
-                        ((unsigned int *)(__src + __ptrDelta))[1] = ((unsigned int *)__src)[1];
-                        __src += 8;
-                    }
-                    while (__src <= __srcLast) {
-                        /* copy over bytes */
-                        __src[__ptrDelta] = __src[0];
-                        __src ++;
-                    }
-                    goto doneSource;
-                }
-            }
-
-            __srcLastX = __srcLastX + 4;
-            if (__src <= __srcLastX) {
-                unsigned int __sum, __digit;
-
-                __digit = ((unsigned *)__src)[0];
-
-                asm ("addl %%eax,%%edx  \n\
-                      movl $0,%%eax     \n\
-                      adcl $0,%%eax"
-                        : "=a"  ((unsigned long)(__carry)),
-                          "=d"  ((unsigned long)(__sum))
-                        : "0"   ((unsigned long)(__carry)),
-                          "1"   (__digit) );
-
-                ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
-                __src += 4;
-
-                if (__carry == 0) {
-                    while (__src <= __srcLast) {
-                        /* copy over bytes */
-                        __src[__ptrDelta] = __src[0];
-                        __src ++;
-                    }
-                    goto doneSource;
-                }
-            }
-        }
+	{
+	    unsigned char *__srcLastX;
+
+	    __srcLastX = __srcLast - 3 - 4;
+	    while (__src <= __srcLastX) {
+		unsigned int __sum, __sum2;
+		unsigned __digit1, __digit2;
+
+		__digit1 = ((unsigned *)__src)[0];
+		__digit2 = ((unsigned *)__src)[1];
+		asm ("addl %%edx,%%ecx          \n\
+		      adcl $0, %%eax            \n\
+		      movl $0, %%edx            \n\
+		      adcl $0, %%edx"
+			: "=d"  ((unsigned long)(__carry)),
+			  "=c"  ((unsigned long)(__sum)),
+			  "=a"  ((unsigned long)(__sum2))
+			: "0"   ((unsigned long)(__carry)),
+			  "1"   (__digit1),
+			  "2"   (__digit2));
+
+		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
+		((unsigned int *)(__src + __ptrDelta))[1] = __sum2;
+
+		__src += 8;
+
+		if (__carry == 0) {
+		    while (__src <= __srcLastX) {
+			/* copy over words */
+			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
+			((unsigned int *)(__src + __ptrDelta))[1] = ((unsigned int *)__src)[1];
+			__src += 8;
+		    }
+		    while (__src <= __srcLast) {
+			/* copy over bytes */
+			__src[__ptrDelta] = __src[0];
+			__src ++;
+		    }
+		    goto doneSource;
+		}
+	    }
+
+	    __srcLastX = __srcLastX + 4;
+	    if (__src <= __srcLastX) {
+		unsigned int __sum, __digit;
+
+		__digit = ((unsigned *)__src)[0];
+
+		asm ("addl %%eax,%%edx  \n\
+		      movl $0,%%eax     \n\
+		      adcl $0,%%eax"
+			: "=a"  ((unsigned long)(__carry)),
+			  "=d"  ((unsigned long)(__sum))
+			: "0"   ((unsigned long)(__carry)),
+			  "1"   (__digit) );
+
+		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
+		__src += 4;
+
+		if (__carry == 0) {
+		    while (__src <= __srcLast) {
+			/* copy over bytes */
+			__src[__ptrDelta] = __src[0];
+			__src ++;
+		    }
+		    goto doneSource;
+		}
+	    }
+	}
 #  endif
 # else /* not i386-GNUC */
 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
-        {
-            unsigned char *__srcLast4;
-
-            /*
-             * add long-wise
-             */
-            __srcLast4 = __srcLast - 3;
-            while (__src <= __srcLast4) {
-                unsigned int __sum;
-
-                __sum = ((unsigned int *)__src)[0];
-                asm {
-                      mov eax, __sum
-                      add eax, __carry
-                      mov edx, 0
-                      adc edx, 0
-                      mov __sum, eax
-                      mov __carry, edx
-                    }
-
-                ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
-                __src += 4;
-                if (__carry == 0) {
-                    while (__src <= __srcLast4) {
-                        /* copy over words */
-                        ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
-                        __src += 4;
-                    }
-                    while (__src <= __srcLast) {
-                        /* copy over bytes */
-                        __src[__ptrDelta] = __src[0];
-                        __src ++;
-                    }
-                    goto doneSource;
-                }
-            }
-        }
+	{
+	    unsigned char *__srcLast4;
+
+	    /*
+	     * add long-wise
+	     */
+	    __srcLast4 = __srcLast - 3;
+	    while (__src <= __srcLast4) {
+		unsigned int __sum;
+
+		__sum = ((unsigned int *)__src)[0];
+		asm {
+		      mov eax, __sum
+		      add eax, __carry
+		      mov edx, 0
+		      adc edx, 0
+		      mov __sum, eax
+		      mov __carry, edx
+		    }
+
+		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
+		__src += 4;
+		if (__carry == 0) {
+		    while (__src <= __srcLast4) {
+			/* copy over words */
+			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
+			__src += 4;
+		    }
+		    while (__src <= __srcLast) {
+			/* copy over bytes */
+			__src[__ptrDelta] = __src[0];
+			__src ++;
+		    }
+		    goto doneSource;
+		}
+	    }
+	}
 #  else /* not i386-WIN32 */
 #   if defined(__LSBFIRST__) && (__POINTER_SIZE__ == 8)
-        {
-            unsigned char *__srcLast4;
-
-            /*
-             * add long-wise
-             */
-            __srcLast4 = __srcLast - 3;
-            while (__src <= __srcLast4) {
-                unsigned INT __sum;
-
-                __sum = ((unsigned int *)__src)[0] + __carry;
-                ((unsigned int *)(__src + __ptrDelta))[0] = __sum /* & 0xFFFF */;
-                __src += 4;
-                __carry = __sum >> 32;
-                if (__carry == 0) {
-                    while (__src <= __srcLast4) {
-                        /* copy over words */
-                        ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
-                        __src += 4;
-                    }
-                    while (__src <= __srcLast) {
-                        /* copy over bytes */
-                        __src[__ptrDelta] = __src[0];
-                        __src ++;
-                    }
-                    goto doneSource;
-                }
-            }
-        }
+	{
+	    unsigned char *__srcLast4;
+
+	    /*
+	     * add long-wise
+	     */
+	    __srcLast4 = __srcLast - 3;
+	    while (__src <= __srcLast4) {
+		unsigned INT __sum;
+
+		__sum = ((unsigned int *)__src)[0] + __carry;
+		((unsigned int *)(__src + __ptrDelta))[0] = __sum /* & 0xFFFF */;
+		__src += 4;
+		__carry = __sum >> 32;
+		if (__carry == 0) {
+		    while (__src <= __srcLast4) {
+			/* copy over words */
+			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
+			__src += 4;
+		    }
+		    while (__src <= __srcLast) {
+			/* copy over bytes */
+			__src[__ptrDelta] = __src[0];
+			__src ++;
+		    }
+		    goto doneSource;
+		}
+	    }
+	}
 #   endif /* LSB+64bit */
 #  endif /* __i386__ & WIN32 */
 # endif /* __i386__ & GNUC */
 
-        /*
-         * add short-wise
-         */
-        while (__src < __srcLast) {
-            __carry += ((unsigned short *)__src)[0];
-            ((unsigned short *)(__src + __ptrDelta))[0] = __carry /* & 0xFFFF */;
-            __carry >>= 16;
-            __src += 2;
-        }
-        /*
-         * last (odd) byte
-         */
-        if (__src <= __srcLast) {
-            __carry += __src[0];
-            __src[__ptrDelta] = __carry /* & 0xFF */;
-            __carry >>= 8;
-            __src++;
-        }
+	/*
+	 * add short-wise
+	 */
+	while (__src < __srcLast) {
+	    __carry += ((unsigned short *)__src)[0];
+	    ((unsigned short *)(__src + __ptrDelta))[0] = __carry /* & 0xFFFF */;
+	    __carry >>= 16;
+	    __src += 2;
+	}
+	/*
+	 * last (odd) byte
+	 */
+	if (__src <= __srcLast) {
+	    __carry += __src[0];
+	    __src[__ptrDelta] = __carry /* & 0xFF */;
+	    __carry >>= 8;
+	    __src++;
+	}
 #else /* not __LSBFIRST__ */
 
-        /*
-         * add byte-wise
-         */
-        while (__src <= __srcLast) {
-            __carry += __src[0];
-            __src[__ptrDelta] = __carry /* & 0xFF */;
-            __src++;
-            __carry >>= 8;
-
-            if (__carry == 0) {
-                while (__src <= __srcLast) {
-                    /* copy over rest */
-                    __src[__ptrDelta] = __src[0];
-                    __src++;
-                }
-                goto doneSource;
-            }
-        }
+	/*
+	 * add byte-wise
+	 */
+	while (__src <= __srcLast) {
+	    __carry += __src[0];
+	    __src[__ptrDelta] = __carry /* & 0xFF */;
+	    __src++;
+	    __carry >>= 8;
+
+	    if (__carry == 0) {
+		while (__src <= __srcLast) {
+		    /* copy over rest */
+		    __src[__ptrDelta] = __src[0];
+		    __src++;
+		}
+		goto doneSource;
+	    }
+	}
 #endif /* __LSBFIRST__ */
 
     doneSource: ;
-        /*
-         * now, at most one other byte is to be stored ...
-         */
-        if (__len < __rsltLen) {
-            __src[__ptrDelta] = __carry /* & 0xFF */;
-            __src++;
-        }
-
-        if (__src[__ptrDelta-1]) {      /* lastDigit */
-            RETURN (result);
-        }
-        ok = true;
+	/*
+	 * now, at most one other byte is to be stored ...
+	 */
+	if (__len < __rsltLen) {
+	    __src[__ptrDelta] = __carry /* & 0xFF */;
+	    __src++;
+	}
+
+	if (__src[__ptrDelta-1]) {      /* lastDigit */
+	    RETURN (result);
+	}
+	ok = true;
     }
 %}.
 
     ok ~~ true ifTrue:[
-        index := 1.
-        carry := aSmallInteger abs.
-
-        [carry ~~ 0] whileTrue:[
-            (index <= len) ifTrue:[
-                carry := (digitByteArray basicAt:index) + carry.
-            ].
-            resultDigitByteArray basicAt:index put:(lastDigit := carry bitAnd:16rFF).
-            carry := carry bitShift:-8.
-            index := index + 1
-        ].
-
-        (index <= rsltLen) ifTrue:[
-            [index <= len] whileTrue:[
-                resultDigitByteArray basicAt:index put:(digitByteArray basicAt:index).
-                index := index + 1
-            ].
-            lastDigit := 0.
-        ].
-
-        (lastDigit ~~ 0 and:[rsltLen > SmallInteger maxBytes]) ifTrue:[
-            ^ result
-        ].
+	index := 1.
+	carry := aSmallInteger abs.
+
+	[carry ~~ 0] whileTrue:[
+	    (index <= len) ifTrue:[
+		carry := (digitByteArray basicAt:index) + carry.
+	    ].
+	    resultDigitByteArray basicAt:index put:(lastDigit := carry bitAnd:16rFF).
+	    carry := carry bitShift:-8.
+	    index := index + 1
+	].
+
+	(index <= rsltLen) ifTrue:[
+	    [index <= len] whileTrue:[
+		resultDigitByteArray basicAt:index put:(digitByteArray basicAt:index).
+		index := index + 1
+	    ].
+	    lastDigit := 0.
+	].
+
+	(lastDigit ~~ 0 and:[rsltLen > SmallInteger maxBytes]) ifTrue:[
+	    ^ result
+	].
     ].
 
     ^ result compressed
@@ -3799,9 +3817,9 @@
     len2 := otherDigitByteArray size.
 
     len1 > len2 ifTrue:[
-        lResult := len1
+	lResult := len1
     ] ifFalse:[
-        lResult := (len1 max: len2) + 1.
+	lResult := (len1 max: len2) + 1.
     ].
     result := self class basicNew numberOfDigits:lResult sign:newSign.
     resultDigitByteArray := result digitBytes.
@@ -3814,202 +3832,202 @@
     if (__isByteArray(_digitByteArray)
      && __isByteArray(otherDigitByteArray)
      && __isByteArray(resultDigitByteArray)) {
-        int __len1 = __intVal(len1);
-        int __len2 = __intVal(len2);
-        int __minLen = __len1 < __len2 ? __len1 : __len2;
-        int __index, __borrow = 0;
-        INT __diff;
-        unsigned char *__myDigits, *__otherDigits, *__resultDigits;
-
-        ok = true;
-
-        __resultDigits = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
-        __otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
-        __myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
-
-        __index = 1;
+	int __len1 = __intVal(len1);
+	int __len2 = __intVal(len2);
+	int __minLen = __len1 < __len2 ? __len1 : __len2;
+	int __index, __borrow = 0;
+	INT __diff;
+	unsigned char *__myDigits, *__otherDigits, *__resultDigits;
+
+	ok = true;
+
+	__resultDigits = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
+	__otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
+	__myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
+
+	__index = 1;
 
 #if defined(__LSBFIRST__)
 # if __POINTER_SIZE__ == 8
-        /*
-         * subtract int-wise
-         */
-        while ((__index+3) <= __minLen) {
-            /* do not make this into one expression - ask cg why */
-            __diff = ((unsigned int *)(__myDigits+__index-1))[0];
-            __diff -= ((unsigned int *)(__otherDigits+__index-1))[0];
-            __diff -= __borrow;
-
-            if (__diff >= 0) {
-                __borrow = 0;
-            } else {
-                __borrow = 1;
-                /* __diff += 0x10000; */
-            }
-            ((unsigned int *)(__resultDigits+__index-1))[0] = __diff;
-            __index += 4;
-        }
+	/*
+	 * subtract int-wise
+	 */
+	while ((__index+3) <= __minLen) {
+	    /* do not make this into one expression - ask cg why */
+	    __diff = ((unsigned int *)(__myDigits+__index-1))[0];
+	    __diff -= ((unsigned int *)(__otherDigits+__index-1))[0];
+	    __diff -= __borrow;
+
+	    if (__diff >= 0) {
+		__borrow = 0;
+	    } else {
+		__borrow = 1;
+		/* __diff += 0x10000; */
+	    }
+	    ((unsigned int *)(__resultDigits+__index-1))[0] = __diff;
+	    __index += 4;
+	}
 # endif /* 64bit */
 
-        /*
-         * subtract short-wise
-         */
-        while (__index < __minLen) {   /* i.e. index+1 <= minLen */
-            /* do not make this into one expression - ask cg why */
-            __diff = ((unsigned short *)(__myDigits+__index-1))[0];
-            __diff -= ((unsigned short *)(__otherDigits+__index-1))[0];
-            __diff -= __borrow;
-            if (__diff >= 0) {
-                __borrow = 0;
-            } else {
-                __borrow = 1;
-                /* __diff += 0x10000; */
-            }
-            ((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
-            __index += 2;
-        }
-
-        if (__index == __minLen) {
-            /* one of the operands has odd length - cannot continue short-wise */
-        } else {
-            if (__len1 > __len2) {
-                while (__index < __len1) {
-                    /* do not make this into one expression - ask cg why */
-                    __diff = ((unsigned short *)(__myDigits+__index-1))[0];
-                    __diff -= __borrow;
-                    if (__diff >= 0) {
-                        __borrow = 0;
-                        ((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
-                        __index += 2;
-
-                        /* copy over rest */
-                        while (__index < __len1) {
-                            ((unsigned short *)(__resultDigits+__index-1))[0] = ((unsigned short *)(__myDigits+__index-1))[0];
-                            __index+=2;
-                        }
-                        if (__index <= __len1) {
-                            __resultDigits[__index-1] = __myDigits[__index-1];
-                            __index++;
-                        }
-                        break;
-                    }
-                    __borrow = 1;
-                    /* __diff += 0x10000; */
-                    ((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
-                    __index += 2;
-                }
-            } else {
-                if (__len2 > __len1) {
-                    while (__index < __len2) {
-                        /* do not make this into one expression - ask cg why */
-                        __diff = 0;
-                        __diff -= ((unsigned short *)(__otherDigits+__index-1))[0];
-                        __diff -= __borrow;
-                        if (__diff >= 0) {
-                            __borrow = 0;
-                        } else {
-                            __borrow = 1;
-                            /* __diff += 0x10000; */
-                        }
-                        ((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
-                        __index += 2;
-                    }
-                }
-            }
-        }
+	/*
+	 * subtract short-wise
+	 */
+	while (__index < __minLen) {   /* i.e. index+1 <= minLen */
+	    /* do not make this into one expression - ask cg why */
+	    __diff = ((unsigned short *)(__myDigits+__index-1))[0];
+	    __diff -= ((unsigned short *)(__otherDigits+__index-1))[0];
+	    __diff -= __borrow;
+	    if (__diff >= 0) {
+		__borrow = 0;
+	    } else {
+		__borrow = 1;
+		/* __diff += 0x10000; */
+	    }
+	    ((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
+	    __index += 2;
+	}
+
+	if (__index == __minLen) {
+	    /* one of the operands has odd length - cannot continue short-wise */
+	} else {
+	    if (__len1 > __len2) {
+		while (__index < __len1) {
+		    /* do not make this into one expression - ask cg why */
+		    __diff = ((unsigned short *)(__myDigits+__index-1))[0];
+		    __diff -= __borrow;
+		    if (__diff >= 0) {
+			__borrow = 0;
+			((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
+			__index += 2;
+
+			/* copy over rest */
+			while (__index < __len1) {
+			    ((unsigned short *)(__resultDigits+__index-1))[0] = ((unsigned short *)(__myDigits+__index-1))[0];
+			    __index+=2;
+			}
+			if (__index <= __len1) {
+			    __resultDigits[__index-1] = __myDigits[__index-1];
+			    __index++;
+			}
+			break;
+		    }
+		    __borrow = 1;
+		    /* __diff += 0x10000; */
+		    ((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
+		    __index += 2;
+		}
+	    } else {
+		if (__len2 > __len1) {
+		    while (__index < __len2) {
+			/* do not make this into one expression - ask cg why */
+			__diff = 0;
+			__diff -= ((unsigned short *)(__otherDigits+__index-1))[0];
+			__diff -= __borrow;
+			if (__diff >= 0) {
+			    __borrow = 0;
+			} else {
+			    __borrow = 1;
+			    /* __diff += 0x10000; */
+			}
+			((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
+			__index += 2;
+		    }
+		}
+	    }
+	}
 #endif
-        /*
-         * subtract byte-wise
-         */
-        while (__index <= __minLen) {
-            /* do not make this into one expression - ask cg why */
-            __diff = __myDigits[__index-1];
-            __diff -= __otherDigits[__index-1];
-            __diff -= __borrow;
-            if (__diff >= 0) {
-                __borrow = 0;
-            } else {
-                __borrow = 1;
-                /* __diff += 0x100; */
-            }
-            __resultDigits[__index-1] = __diff;
-            __index++;
-        }
-
-        if (__len1 > __len2) {
-            while (__index <= __len1) {
-                /* do not make this into one expression - ask cg why */
-                __diff = __myDigits[__index-1];
-                __diff -= __borrow;
-                if (__diff >= 0) {
-                    __borrow = 0;
-                    /* copy over rest */
-                    __resultDigits[__index-1] = __diff;
-                    __index++;
-                    while (__index <= __len1) {
-                        __resultDigits[__index-1] = __myDigits[__index-1];
-                        __index++;
-                    }
-                    break;
-                }
-                __borrow = 1;
-                /* __diff += 0x100; */
-                __resultDigits[__index-1] = __diff;
-                __index++;
-            }
-        } else {
-            if (__len2 > __len1) {
-                while (__index <= __len2) {
-                    /* do not make this into one expression - ask cg why */
-                    __diff = 0;
-                    __diff -= __otherDigits[__index-1];
-                    __diff -= __borrow;
-                    if (__diff >= 0) {
-                        __borrow = 0;
-                    } else {
-                        __borrow = 1;
-                        /* __diff += 0x100; */
-                    }
-                    __resultDigits[__index-1] = __diff;
-                    __index++;
-                }
-            }
-        }
-        borrow = __mkSmallInteger(__borrow);
-        index = __mkSmallInteger(__index);
-        lastDigit = __mkSmallInteger(__resultDigits[__intVal(lResult)-1]);
+	/*
+	 * subtract byte-wise
+	 */
+	while (__index <= __minLen) {
+	    /* do not make this into one expression - ask cg why */
+	    __diff = __myDigits[__index-1];
+	    __diff -= __otherDigits[__index-1];
+	    __diff -= __borrow;
+	    if (__diff >= 0) {
+		__borrow = 0;
+	    } else {
+		__borrow = 1;
+		/* __diff += 0x100; */
+	    }
+	    __resultDigits[__index-1] = __diff;
+	    __index++;
+	}
+
+	if (__len1 > __len2) {
+	    while (__index <= __len1) {
+		/* do not make this into one expression - ask cg why */
+		__diff = __myDigits[__index-1];
+		__diff -= __borrow;
+		if (__diff >= 0) {
+		    __borrow = 0;
+		    /* copy over rest */
+		    __resultDigits[__index-1] = __diff;
+		    __index++;
+		    while (__index <= __len1) {
+			__resultDigits[__index-1] = __myDigits[__index-1];
+			__index++;
+		    }
+		    break;
+		}
+		__borrow = 1;
+		/* __diff += 0x100; */
+		__resultDigits[__index-1] = __diff;
+		__index++;
+	    }
+	} else {
+	    if (__len2 > __len1) {
+		while (__index <= __len2) {
+		    /* do not make this into one expression - ask cg why */
+		    __diff = 0;
+		    __diff -= __otherDigits[__index-1];
+		    __diff -= __borrow;
+		    if (__diff >= 0) {
+			__borrow = 0;
+		    } else {
+			__borrow = 1;
+			/* __diff += 0x100; */
+		    }
+		    __resultDigits[__index-1] = __diff;
+		    __index++;
+		}
+	    }
+	}
+	borrow = __mkSmallInteger(__borrow);
+	index = __mkSmallInteger(__index);
+	lastDigit = __mkSmallInteger(__resultDigits[__intVal(lResult)-1]);
     }
 %}.
     ok == true ifFalse:[
-        index := 1.
-        borrow := 0.
-
-        done := false.
-        [done] whileFalse:[
-            diff := borrow.
-            (index <= len1) ifTrue:[
-                diff := diff + (digitByteArray basicAt:index).
-                (index <= len2) ifTrue:[
-                    diff := diff - (otherDigitByteArray basicAt:index)
-                ]
-            ] ifFalse:[
-                (index <= len2) ifTrue:[
-                    diff := diff - (otherDigitByteArray basicAt:index)
-                ] ifFalse:[
-                    "end reached"
-                    done := true
-                ]
-            ].
-
-            "/ workaround for
-            "/ gcc code generator bug
-
-            (diff >= 0) ifTrue:[
-                borrow := 0
-            ] ifFalse:[
-                borrow := -1.
-                diff := diff + 16r100
-            ].
+	index := 1.
+	borrow := 0.
+
+	done := false.
+	[done] whileFalse:[
+	    diff := borrow.
+	    (index <= len1) ifTrue:[
+		diff := diff + (digitByteArray basicAt:index).
+		(index <= len2) ifTrue:[
+		    diff := diff - (otherDigitByteArray basicAt:index)
+		]
+	    ] ifFalse:[
+		(index <= len2) ifTrue:[
+		    diff := diff - (otherDigitByteArray basicAt:index)
+		] ifFalse:[
+		    "end reached"
+		    done := true
+		]
+	    ].
+
+	    "/ workaround for
+	    "/ gcc code generator bug
+
+	    (diff >= 0) ifTrue:[
+		borrow := 0
+	    ] ifFalse:[
+		borrow := -1.
+		diff := diff + 16r100
+	    ].
 
     "/        (diff < 0) ifTrue:[
     "/            borrow := -1.
@@ -4018,40 +4036,40 @@
     "/            borrow := 0
     "/        ].
 
-            resultDigitByteArray basicAt:index put:diff.
-            index := index + 1
-        ].
-        lastDigit := resultDigitByteArray basicAt:lResult.
+	    resultDigitByteArray basicAt:index put:diff.
+	    index := index + 1
+	].
+	lastDigit := resultDigitByteArray basicAt:lResult.
     ].
 
     (borrow ~~ 0) ifTrue:[
-        "/ must generate 255's complement
-
-        result sign:newSign negated.
-        [index <= lResult] whileTrue:[
-            resultDigitByteArray basicAt:index put:16rFF.
-            index := index + 1.
-        ].
-        index := lResult.
-        [index > 0] whileTrue:[
-            resultDigitByteArray basicAt:index put:(255 - (resultDigitByteArray at:index)).
-            index := index - 1.
-        ].
-
-        index := 1.
-        carry := 1.
-        [carry ~~ 0] whileTrue:[
-            (index <= lResult) ifTrue:[
-                carry := (resultDigitByteArray basicAt:index) + carry.
-            ].
-            resultDigitByteArray basicAt:index put:(carry bitAnd:16rFF).
-            carry := carry bitShift:-8.
-            index := index + 1
-        ].
-        lastDigit := resultDigitByteArray basicAt:lResult.
+	"/ must generate 255's complement
+
+	result sign:newSign negated.
+	[index <= lResult] whileTrue:[
+	    resultDigitByteArray basicAt:index put:16rFF.
+	    index := index + 1.
+	].
+	index := lResult.
+	[index > 0] whileTrue:[
+	    resultDigitByteArray basicAt:index put:(255 - (resultDigitByteArray at:index)).
+	    index := index - 1.
+	].
+
+	index := 1.
+	carry := 1.
+	[carry ~~ 0] whileTrue:[
+	    (index <= lResult) ifTrue:[
+		carry := (resultDigitByteArray basicAt:index) + carry.
+	    ].
+	    resultDigitByteArray basicAt:index put:(carry bitAnd:16rFF).
+	    carry := carry bitShift:-8.
+	    index := index + 1
+	].
+	lastDigit := resultDigitByteArray basicAt:lResult.
     ].
     (lastDigit == 0 or:[lResult <= SmallInteger maxBytes]) ifTrue:[
-        ^ result compressed.
+	^ result compressed.
     ].
     ^ result
 
@@ -4429,494 +4447,494 @@
 
     if (__isByteArray(_digitByteArray)
      && __isByteArray(otherDigitByteArray)) {
-        int _len1, _len2, _newLen;
-        unsigned char *_myDigits, *_otherDigits, *_newDigits;
-        int _index, _carry;
-        int _comLen;
-
-        _len1 = __byteArraySize(_digitByteArray);
-        _len2 = __byteArraySize(otherDigitByteArray);
-
-        _otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
-        _myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
-
-        if (_len1 < _len2) {
-            _comLen = _len1;
-            _newLen = _len2;
-            if (_otherDigits[_len2 - 1] == 0xFF) _newLen++;
-        } else if (_len2 < _len1) {
-            _comLen = _len2;
-            _newLen = _len1;
-            if (_myDigits[_len1 - 1] == 0xFF) _newLen++;
-        } else {
-            /*
-             * there can only be an overflow from the high bytes,
-             * if their sum is >= 255
-             * (with sum==255, a carry could still occur from the next lower bytes)
-             */
-            _newLen = _len1;
-            if ((_otherDigits[_len2 - 1] + _myDigits[_len1 - 1]) >= 0xFF) {
-                _newLen++;
-            } else {
-                if (_newLen == sizeof(INT)) {
-                    OBJ _uint;
-
-                    /*
-                     * two word-sized numbers, no carry - a very common case ...
-                     */
+	int _len1, _len2, _newLen;
+	unsigned char *_myDigits, *_otherDigits, *_newDigits;
+	int _index, _carry;
+	int _comLen;
+
+	_len1 = __byteArraySize(_digitByteArray);
+	_len2 = __byteArraySize(otherDigitByteArray);
+
+	_otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
+	_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
+
+	if (_len1 < _len2) {
+	    _comLen = _len1;
+	    _newLen = _len2;
+	    if (_otherDigits[_len2 - 1] == 0xFF) _newLen++;
+	} else if (_len2 < _len1) {
+	    _comLen = _len2;
+	    _newLen = _len1;
+	    if (_myDigits[_len1 - 1] == 0xFF) _newLen++;
+	} else {
+	    /*
+	     * there can only be an overflow from the high bytes,
+	     * if their sum is >= 255
+	     * (with sum==255, a carry could still occur from the next lower bytes)
+	     */
+	    _newLen = _len1;
+	    if ((_otherDigits[_len2 - 1] + _myDigits[_len1 - 1]) >= 0xFF) {
+		_newLen++;
+	    } else {
+		if (_newLen == sizeof(INT)) {
+		    OBJ _uint;
+
+		    /*
+		     * two word-sized numbers, no carry - a very common case ...
+		     */
 #if defined(__LSB_FIRST__)
-                    unsigned INT _sum = *(unsigned INT *)_otherDigits + *(unsigned INT *)_myDigits;
+		    unsigned INT _sum = *(unsigned INT *)_otherDigits + *(unsigned INT *)_myDigits;
 #else
-                    unsigned INT _sum = __unsignedLongIntVal(self) + __unsignedLongIntVal(aLargeInteger);
+		    unsigned INT _sum = __unsignedLongIntVal(self) + __unsignedLongIntVal(aLargeInteger);
 #endif /* not LSB_FIRST */
-                    if (_sum <= _MAX_INT) {
-                        _uint = __mkSmallInteger(_sum * __intVal(newSign));
-                    } else {
-                        _uint = __MKULARGEINT(_sum);
-                        __LargeIntegerInstPtr(_uint)->l_sign = newSign;
-                    }
-                    RETURN (_uint);
-                }
-            }
-            _comLen = _len1;
-        }
-        resultDigitByteArray = __BYTEARRAY_UNINITIALIZED_NEW_INT(_newLen);
-
-        /*
-         * must refetch - GC could have been invoked
-         */
-        _digitByteArray = __INST(digitByteArray);
-
-        _myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
-        _otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
-        _newDigits = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
-
-        /*
-         * add them ...
-         */
-        _index = 1;
-        _carry = 0;
+		    if (_sum <= _MAX_INT) {
+			_uint = __mkSmallInteger(_sum * __intVal(newSign));
+		    } else {
+			_uint = __MKULARGEINT(_sum);
+			__LargeIntegerInstPtr(_uint)->l_sign = newSign;
+		    }
+		    RETURN (_uint);
+		}
+	    }
+	    _comLen = _len1;
+	}
+	resultDigitByteArray = __BYTEARRAY_UNINITIALIZED_NEW_INT(_newLen);
+
+	/*
+	 * must refetch - GC could have been invoked
+	 */
+	_digitByteArray = __INST(digitByteArray);
+
+	_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
+	_otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
+	_newDigits = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
+
+	/*
+	 * add them ...
+	 */
+	_index = 1;
+	_carry = 0;
 
 #if defined(__LSBFIRST__)
 # if (__POINTER_SIZE__ == 8) && defined(__GNUC__)
 #  if 0  /* not faster (on alpha) */
-        {
-            int _comLen7;
-
-            /*
-             * have a 64bit integers;
-             * add quad-wise
-             * accessing bytes at: [index-1][index][index+1]..[index+6]
-             */
-            _comLen7 = _comLen - 3 - 4;
-            while (_index <= _comLen7) {
-                UINT64 _sum, _t1, _t2;
-
-                asm ("addq   %5,%6,%1         /* sum */                  \n\
-                      addq   %0,%1,%1         /* plus carryIn */         \n\
-                      cmpult %1,%5,%2         /* was there a carry ? */  \n\
-                      cmpult %1,%6,%3         /* was there a carry ? */  \n\
-                      bis    %2,%3,%0         /* carryOut */             \n\
-                     "
-                        : "=r"  (_carry),
-                          "=r"  (_sum),
-                          "r"   (_t1),
-                          "r"   (_t2)
-                        : "r"   (_carry),
-                          "r"   (((unsigned long *)(&(_myDigits[_index - 1])))[0]),
-                          "r"   (((unsigned long *)(&(_otherDigits[_index - 1])))[0])
-                    );
-                /* _sum = _sum & 0xFFFFFFFF; */
-                ((unsigned long *)(&(_newDigits[_index - 1])))[0] = _sum;
-                _index += 8;
-            }
-        }
+	{
+	    int _comLen7;
+
+	    /*
+	     * have a 64bit integers;
+	     * add quad-wise
+	     * accessing bytes at: [index-1][index][index+1]..[index+6]
+	     */
+	    _comLen7 = _comLen - 3 - 4;
+	    while (_index <= _comLen7) {
+		UINT64 _sum, _t1, _t2;
+
+		asm ("addq   %5,%6,%1         /* sum */                  \n\
+		      addq   %0,%1,%1         /* plus carryIn */         \n\
+		      cmpult %1,%5,%2         /* was there a carry ? */  \n\
+		      cmpult %1,%6,%3         /* was there a carry ? */  \n\
+		      bis    %2,%3,%0         /* carryOut */             \n\
+		     "
+			: "=r"  (_carry),
+			  "=r"  (_sum),
+			  "r"   (_t1),
+			  "r"   (_t2)
+			: "r"   (_carry),
+			  "r"   (((unsigned long *)(&(_myDigits[_index - 1])))[0]),
+			  "r"   (((unsigned long *)(&(_otherDigits[_index - 1])))[0])
+		    );
+		/* _sum = _sum & 0xFFFFFFFF; */
+		((unsigned long *)(&(_newDigits[_index - 1])))[0] = _sum;
+		_index += 8;
+	    }
+	}
 #  endif
 # endif /* 64bit */
 
 # if (__POINTER_SIZE__ == 8)
 # if 0  /* not faster (on alpha) */
-        {
-            int _comLen7;
-
-            /*
-             * have a 64bit integers;
-             * add quad-wise
-             * accessing bytes at: [index-1][index][index+1]..[index+6]
-             */
-            _comLen7 = _comLen - 3 - 4;
-            while (_index <= _comLen7) {
-                UINT64 _sum, _t1, _t2;
-
-                _t1 = ((UINT64 *)(&(_myDigits[_index - 1])))[0];
-                _t2 = ((UINT64 *)(&(_otherDigits[_index - 1])))[0];
-                _sum = _t1 + _t2 + _carry;
-                ((UINT64 *)(&(_newDigits[_index - 1])))[0] = _sum;
-                _carry = (_sum < _t1) | (_sum < _t2);
-                _index += 8;
-            }
-        }
+	{
+	    int _comLen7;
+
+	    /*
+	     * have a 64bit integers;
+	     * add quad-wise
+	     * accessing bytes at: [index-1][index][index+1]..[index+6]
+	     */
+	    _comLen7 = _comLen - 3 - 4;
+	    while (_index <= _comLen7) {
+		UINT64 _sum, _t1, _t2;
+
+		_t1 = ((UINT64 *)(&(_myDigits[_index - 1])))[0];
+		_t2 = ((UINT64 *)(&(_otherDigits[_index - 1])))[0];
+		_sum = _t1 + _t2 + _carry;
+		((UINT64 *)(&(_newDigits[_index - 1])))[0] = _sum;
+		_carry = (_sum < _t1) | (_sum < _t2);
+		_index += 8;
+	    }
+	}
 #  endif
 # endif /* 64bit */
 
 # ifdef UINT64
-        {
-            int _comLen3;
-
-            /*
-             * have a 64bit integer type;
-             * add int-wise
-             * accessing bytes at: [index-1][index][index+1][index+2]
-             */
-            _comLen3 = _comLen - 3;
-            while (_index <= _comLen3) {
-                UINT64 _sum;
-
-                /* do not merge the 3 lines below into one -
-                 * (will do sign extension then, which is wrong here)
-                 */
-                _sum = (unsigned)_carry;
-                _sum += ((unsigned int *)(&(_myDigits[_index - 1])))[0];
-                _sum += ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
-                _carry = _sum >> 32;
-                /* _sum = _sum & 0xFFFFFFFF; */
-                ((unsigned int *)(&(_newDigits[_index - 1])))[0] = _sum;
-                _index += 4;
-            }
-        }
+	{
+	    int _comLen3;
+
+	    /*
+	     * have a 64bit integer type;
+	     * add int-wise
+	     * accessing bytes at: [index-1][index][index+1][index+2]
+	     */
+	    _comLen3 = _comLen - 3;
+	    while (_index <= _comLen3) {
+		UINT64 _sum;
+
+		/* do not merge the 3 lines below into one -
+		 * (will do sign extension then, which is wrong here)
+		 */
+		_sum = (unsigned)_carry;
+		_sum += ((unsigned int *)(&(_myDigits[_index - 1])))[0];
+		_sum += ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
+		_carry = _sum >> 32;
+		/* _sum = _sum & 0xFFFFFFFF; */
+		((unsigned int *)(&(_newDigits[_index - 1])))[0] = _sum;
+		_index += 4;
+	    }
+	}
 # else
 #  if defined(__i386__) && defined(__GNUC__) && (__POINTER_SIZE__ == 4)
-        {
-            int _comLen3;
-
-            _comLen3 = _comLen - 3 - 4;
-            while (_index <= _comLen3) {
-                unsigned int _sum, _sum2;
-                unsigned int __in1A, __in1B, __in2A, __in2B;
-
-                __in1A = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
-                __in2A = ((unsigned int *)(&(_myDigits[_index - 1])))[1];
-                __in1B = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
-                __in2B = ((unsigned int *)(&(_otherDigits[_index - 1])))[1];
-
-                asm ("addl %%edx,%%eax  \n\
-                      movl $0,%%edx     \n\
-                      adcl $0,%%edx     \n\
-                      addl %5,%%eax     \n\
-                      adcl $0,%%edx     \n\
-                                        \n\
-                      addl %%edx,%%ecx  \n\
-                      movl $0,%%edx     \n\
-                      adcl $0,%%edx     \n\
-                      addl %7,%%ecx     \n\
-                      adcl $0,%%edx     \n\
-                     "
-                        : "=d"  (_carry),
-                          "=a"  (_sum),
-                          "=c"  (_sum2)
-                        : "0"   (_carry),
-                          "1"   (__in1A),
-                          "rm"  (__in1B),
-                          "2"   (__in2A),
-                          "rm"  (__in2B)
-                    );
-
-                ((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
-                ((unsigned *)(&(_newDigits[_index - 1])))[1] = _sum2;
-                _index += 8;
-            }
-            /*
-             * add int-wise
-             * accessing bytes at: [index-1][index][index+1][index+2]
-             */
-            _comLen3 = _comLen3 + 4;
-            if (_index <= _comLen3) {
-                unsigned int _sum;
-                unsigned int __inA, __inB;
-
-                __inA = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
-                __inB = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
-
-                asm ("addl %%edx,%%eax      \n\
-                      movl $0,%%edx         \n\
-                      adcl $0,%%edx         \n\
-                      addl %4,%%eax         \n\
-                      adcl $0,%%edx"
-                        : "=d"  (_carry),
-                          "=a"  (_sum)
-                        : "0"   (_carry),
-                          "1"   (__inA),
-                          "rm"  (__inB)
-                    );
-
-                ((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
-                _index += 4;
-            }
-        }
+	{
+	    int _comLen3;
+
+	    _comLen3 = _comLen - 3 - 4;
+	    while (_index <= _comLen3) {
+		unsigned int _sum, _sum2;
+		unsigned int __in1A, __in1B, __in2A, __in2B;
+
+		__in1A = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
+		__in2A = ((unsigned int *)(&(_myDigits[_index - 1])))[1];
+		__in1B = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
+		__in2B = ((unsigned int *)(&(_otherDigits[_index - 1])))[1];
+
+		asm ("addl %%edx,%%eax  \n\
+		      movl $0,%%edx     \n\
+		      adcl $0,%%edx     \n\
+		      addl %5,%%eax     \n\
+		      adcl $0,%%edx     \n\
+					\n\
+		      addl %%edx,%%ecx  \n\
+		      movl $0,%%edx     \n\
+		      adcl $0,%%edx     \n\
+		      addl %7,%%ecx     \n\
+		      adcl $0,%%edx     \n\
+		     "
+			: "=d"  (_carry),
+			  "=a"  (_sum),
+			  "=c"  (_sum2)
+			: "0"   (_carry),
+			  "1"   (__in1A),
+			  "rm"  (__in1B),
+			  "2"   (__in2A),
+			  "rm"  (__in2B)
+		    );
+
+		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
+		((unsigned *)(&(_newDigits[_index - 1])))[1] = _sum2;
+		_index += 8;
+	    }
+	    /*
+	     * add int-wise
+	     * accessing bytes at: [index-1][index][index+1][index+2]
+	     */
+	    _comLen3 = _comLen3 + 4;
+	    if (_index <= _comLen3) {
+		unsigned int _sum;
+		unsigned int __inA, __inB;
+
+		__inA = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
+		__inB = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
+
+		asm ("addl %%edx,%%eax      \n\
+		      movl $0,%%edx         \n\
+		      adcl $0,%%edx         \n\
+		      addl %4,%%eax         \n\
+		      adcl $0,%%edx"
+			: "=d"  (_carry),
+			  "=a"  (_sum)
+			: "0"   (_carry),
+			  "1"   (__inA),
+			  "rm"  (__inB)
+		    );
+
+		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
+		_index += 4;
+	    }
+	}
 #  endif /* __i386__ && GNUC */
 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
-        {
-            int _comLen3;
-
-            /*
-             * add long-wise
-             * accessing bytes at: [index-1][index][index+1][index+2]
-             */
-            _comLen3 = _comLen - 3;
-            while (_index <= _comLen3) {
-                unsigned int _sum, _v1, _v2;
-
-                _v1 = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
-                _v2 = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
-                asm {
-                      mov eax, _v1
-                      add eax, _v2
-                      mov edx, 0
-                      adc edx, 0
-                      add eax, _carry
-                      adc edx, 0
-                      mov _carry, edx
-                      mov _sum, eax
-                    }
-
-                ((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
-                _index += 4;
-            }
-        }
+	{
+	    int _comLen3;
+
+	    /*
+	     * add long-wise
+	     * accessing bytes at: [index-1][index][index+1][index+2]
+	     */
+	    _comLen3 = _comLen - 3;
+	    while (_index <= _comLen3) {
+		unsigned int _sum, _v1, _v2;
+
+		_v1 = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
+		_v2 = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
+		asm {
+		      mov eax, _v1
+		      add eax, _v2
+		      mov edx, 0
+		      adc edx, 0
+		      add eax, _carry
+		      adc edx, 0
+		      mov _carry, edx
+		      mov _sum, eax
+		    }
+
+		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
+		_index += 4;
+	    }
+	}
 #  endif /* __i386__ && WIN32 */
 # endif /* INT64 */
-        /*
-         * add short-wise
-         * accessing bytes at: [index-1][index]
-         */
-        while (_index < _comLen) {
-            unsigned int _sum;
-
-            _sum = _carry
-                   + ((unsigned short *)(&(_myDigits[_index - 1])))[0]
-                   + ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
-            _carry = _sum >> 16;
-            /* _sum = _sum & 0xFFFF; */
-            *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
-            _index += 2;
-        }
+	/*
+	 * add short-wise
+	 * accessing bytes at: [index-1][index]
+	 */
+	while (_index < _comLen) {
+	    unsigned int _sum;
+
+	    _sum = _carry
+		   + ((unsigned short *)(&(_myDigits[_index - 1])))[0]
+		   + ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
+	    _carry = _sum >> 16;
+	    /* _sum = _sum & 0xFFFF; */
+	    *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
+	    _index += 2;
+	}
 #else
 # ifdef __sparc__
-        /*
-         * add short-wise
-         * accessing bytes at: [index-1][index]
-         */
-        while (_index < _comLen) {
-            unsigned int _sum;
-            unsigned short _v1, _v2;
-
-            _v1 = ((unsigned short *)(&(_myDigits[_index - 1])))[0];
-            _v2 = ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
-            _sum = _carry + (_v1>>8) + (_v2>>8);
-            _carry = _sum >> 8;
-            _newDigits[_index - 1] = _sum;
-
-            _sum = _carry + (_v1 & 0xFF) + (_v2 & 0xFF);
-            _carry = _sum >> 8;
-            _newDigits[_index] = _sum;
-            _index += 2;
-        }
+	/*
+	 * add short-wise
+	 * accessing bytes at: [index-1][index]
+	 */
+	while (_index < _comLen) {
+	    unsigned int _sum;
+	    unsigned short _v1, _v2;
+
+	    _v1 = ((unsigned short *)(&(_myDigits[_index - 1])))[0];
+	    _v2 = ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
+	    _sum = _carry + (_v1>>8) + (_v2>>8);
+	    _carry = _sum >> 8;
+	    _newDigits[_index - 1] = _sum;
+
+	    _sum = _carry + (_v1 & 0xFF) + (_v2 & 0xFF);
+	    _carry = _sum >> 8;
+	    _newDigits[_index] = _sum;
+	    _index += 2;
+	}
 # endif
 #endif /* __LSBFIRST__ */
 
-        /*
-         * add byte-wise
-         */
-        while (_index <= _comLen) {
-            unsigned int _sum;
-
-            _sum = _carry
-                   + _myDigits[_index - 1]
-                   + _otherDigits[_index - 1];
-            _carry = _sum >> 8;
-            /* _sum = _sum & 0xFF; */
-            _newDigits[_index - 1] = _sum;
-            _index++;
-        }
-
-        /*
-         * rest
-         */
-        if (_len1 > _len2) {
+	/*
+	 * add byte-wise
+	 */
+	while (_index <= _comLen) {
+	    unsigned int _sum;
+
+	    _sum = _carry
+		   + _myDigits[_index - 1]
+		   + _otherDigits[_index - 1];
+	    _carry = _sum >> 8;
+	    /* _sum = _sum & 0xFF; */
+	    _newDigits[_index - 1] = _sum;
+	    _index++;
+	}
+
+	/*
+	 * rest
+	 */
+	if (_len1 > _len2) {
 #if defined(__LSBFIRST__)
-            if (_index <= _len1) {
-                if ((_index - 1) & 1) {
-                    /* odd byte */
-                    unsigned int _sum;
-
-                    _sum = _carry + _myDigits[_index - 1];
-                    _carry = _sum >> 8;
-                    /* _sum = _sum & 0xFF; */
-                    _newDigits[_index - 1] = _sum;
-                    _index++;
-                }
-
-                while (_index < _len1) {
-                    /* shorts */
-                    unsigned int _sum;
-
-                    _sum = _carry + *(unsigned short *)(&(_myDigits[_index - 1]));
-                    _carry = _sum >> 16;
-                    /* _sum = _sum & 0xFFFF; */
-                    *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
-                    _index += 2;
-                }
-
-                if (_index <= _len1) {
-                    /* last byte */
-                    unsigned int _sum;
-
-                    _sum = _carry + _myDigits[_index - 1];
-                    _carry = _sum >> 8;
-                    /* _sum = _sum & 0xFF; */
-                    _newDigits[_index - 1] = _sum;
-                    _index++;
-                }
-            }
+	    if (_index <= _len1) {
+		if ((_index - 1) & 1) {
+		    /* odd byte */
+		    unsigned int _sum;
+
+		    _sum = _carry + _myDigits[_index - 1];
+		    _carry = _sum >> 8;
+		    /* _sum = _sum & 0xFF; */
+		    _newDigits[_index - 1] = _sum;
+		    _index++;
+		}
+
+		while (_index < _len1) {
+		    /* shorts */
+		    unsigned int _sum;
+
+		    _sum = _carry + *(unsigned short *)(&(_myDigits[_index - 1]));
+		    _carry = _sum >> 16;
+		    /* _sum = _sum & 0xFFFF; */
+		    *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
+		    _index += 2;
+		}
+
+		if (_index <= _len1) {
+		    /* last byte */
+		    unsigned int _sum;
+
+		    _sum = _carry + _myDigits[_index - 1];
+		    _carry = _sum >> 8;
+		    /* _sum = _sum & 0xFF; */
+		    _newDigits[_index - 1] = _sum;
+		    _index++;
+		}
+	    }
 #else
-            while (_index <= _len1) {
-                unsigned int _sum;
-
-                _sum = _carry + _myDigits[_index - 1];
-                _carry = _sum >> 8;
-                /* _sum = _sum & 0xFF; */
-                _newDigits[_index - 1] = _sum;
-                _index++;
-            }
+	    while (_index <= _len1) {
+		unsigned int _sum;
+
+		_sum = _carry + _myDigits[_index - 1];
+		_carry = _sum >> 8;
+		/* _sum = _sum & 0xFF; */
+		_newDigits[_index - 1] = _sum;
+		_index++;
+	    }
 #endif /* not LSB */
-        } else {
-            if (_len2 > _len1) {
+	} else {
+	    if (_len2 > _len1) {
 #if defined(__LSBFIRST__)
-                if (_index <= _len2) {
-                    if ((_index - 1) & 1) {
-                        /* odd byte */
-                        unsigned int _sum;
-
-                        _sum = _carry + _otherDigits[_index - 1];
-                        _carry = _sum >> 8;
-                        /* _sum = _sum & 0xFF; */
-                        _newDigits[_index - 1] = _sum;
-                        _index++;
-                    }
-
-                    while (_index < _len2) {
-                        /* shorts */
-                        unsigned int _sum;
-
-                        _sum = _carry + *(unsigned short *)(&(_otherDigits[_index - 1]));
-                        _carry = _sum >> 16;
-                        /* _sum = _sum & 0xFFFF; */
-                        *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
-                        _index += 2;
-                    }
-
-                    if (_index <= _len2) {
-                        /* last byte */
-                        unsigned int _sum;
-
-                        _sum = _carry + _otherDigits[_index - 1];
-                        _carry = _sum >> 8;
-                        /* _sum = _sum & 0xFF; */
-                        _newDigits[_index - 1] = _sum;
-                        _index++;
-                    }
-                }
+		if (_index <= _len2) {
+		    if ((_index - 1) & 1) {
+			/* odd byte */
+			unsigned int _sum;
+
+			_sum = _carry + _otherDigits[_index - 1];
+			_carry = _sum >> 8;
+			/* _sum = _sum & 0xFF; */
+			_newDigits[_index - 1] = _sum;
+			_index++;
+		    }
+
+		    while (_index < _len2) {
+			/* shorts */
+			unsigned int _sum;
+
+			_sum = _carry + *(unsigned short *)(&(_otherDigits[_index - 1]));
+			_carry = _sum >> 16;
+			/* _sum = _sum & 0xFFFF; */
+			*(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
+			_index += 2;
+		    }
+
+		    if (_index <= _len2) {
+			/* last byte */
+			unsigned int _sum;
+
+			_sum = _carry + _otherDigits[_index - 1];
+			_carry = _sum >> 8;
+			/* _sum = _sum & 0xFF; */
+			_newDigits[_index - 1] = _sum;
+			_index++;
+		    }
+		}
 #else
-                while (_index <= _len2) {
-                    unsigned int _sum;
-
-                    _sum = _carry + _otherDigits[_index - 1];
-                    _carry = _sum >> 8;
-                    /* _sum = _sum & 0xFF; */
-                    _newDigits[_index - 1] = _sum;
-                    _index++;
-                }
+		while (_index <= _len2) {
+		    unsigned int _sum;
+
+		    _sum = _carry + _otherDigits[_index - 1];
+		    _carry = _sum >> 8;
+		    /* _sum = _sum & 0xFF; */
+		    _newDigits[_index - 1] = _sum;
+		    _index++;
+		}
 #endif /* not LSB */
-            }
-        }
-
-        while (_index <= _newLen) {
-            unsigned int _sum;
-
-            _sum = _carry;
-            _carry = _sum >> 8;
-            /* _sum = _sum & 0xFF; */
-            _newDigits[_index - 1] = _sum;
-            _index++;
-        }
+	    }
+	}
+
+	while (_index <= _newLen) {
+	    unsigned int _sum;
+
+	    _sum = _carry;
+	    _carry = _sum >> 8;
+	    /* _sum = _sum & 0xFF; */
+	    _newDigits[_index - 1] = _sum;
+	    _index++;
+	}
     }
 %}.
     resultDigitByteArray notNil ifTrue:[
-        result := self class basicNew.
-        result setDigits:resultDigitByteArray.
-        result setSign:newSign.
+	result := self class basicNew.
+	result setDigits:resultDigitByteArray.
+	result setSign:newSign.
     ] ifFalse:[
-        len1 := digitByteArray size.
-        len2 := otherDigitByteArray size.
-
-        "/ earlier versions estimated the newLength as:
-        "/ (len1 max:len2) + 1
-        "/ and reduced the result.
-        "/ however, if one of the addends is smaller,
-        "/ the result will never require another digit,
-        "/ if the highest digit of the larger addent is
-        "/ not equal to 255. Therefore, in most cases,
-        "/ we can avoid the computation and resizing
-        "/ in #reduced.
-
-        len1 < len2 ifTrue:[
-            newLen := len2.
-            (otherDigitByteArray at:len2) == 16rFF ifTrue:[
-                newLen := newLen + 1
-            ]
-        ] ifFalse:[
-            len2 < len1 ifTrue:[
-                newLen := len1.
-                (digitByteArray at:len1) == 16rFF ifTrue:[
-                    newLen := newLen + 1
-                ]
-            ] ifFalse:[
-                newLen := len1 + 1.
-            ]
-        ].
-
-        result := self class basicNew numberOfDigits:newLen.
-        result sign:newSign.
-        resultDigitByteArray := result digitBytes.
-
-        index := 1.
-        carry := 0.
-
-        done := false.
-        [done] whileFalse:[
-            sum := carry.
-            (index <= len1) ifTrue:[
-                sum := sum + (digitByteArray basicAt:index).
-                (index <= len2) ifTrue:[
-                    sum := sum + (otherDigitByteArray basicAt:index)
-                ]
-            ] ifFalse:[
-                (index <= len2) ifTrue:[
-                    sum := sum + (otherDigitByteArray basicAt:index)
-                ] ifFalse:[
-                    "end reached"
-                    done := true
-                ]
-            ].
-            (sum >= 16r100) ifTrue:[
-                carry := 1.
-                sum := sum - 16r100
-            ] ifFalse:[
-                carry := 0
-            ].
-            resultDigitByteArray basicAt:index put:sum.
-            index := index + 1
-        ].
+	len1 := digitByteArray size.
+	len2 := otherDigitByteArray size.
+
+	"/ earlier versions estimated the newLength as:
+	"/ (len1 max:len2) + 1
+	"/ and reduced the result.
+	"/ however, if one of the addends is smaller,
+	"/ the result will never require another digit,
+	"/ if the highest digit of the larger addent is
+	"/ not equal to 255. Therefore, in most cases,
+	"/ we can avoid the computation and resizing
+	"/ in #reduced.
+
+	len1 < len2 ifTrue:[
+	    newLen := len2.
+	    (otherDigitByteArray at:len2) == 16rFF ifTrue:[
+		newLen := newLen + 1
+	    ]
+	] ifFalse:[
+	    len2 < len1 ifTrue:[
+		newLen := len1.
+		(digitByteArray at:len1) == 16rFF ifTrue:[
+		    newLen := newLen + 1
+		]
+	    ] ifFalse:[
+		newLen := len1 + 1.
+	    ]
+	].
+
+	result := self class basicNew numberOfDigits:newLen.
+	result sign:newSign.
+	resultDigitByteArray := result digitBytes.
+
+	index := 1.
+	carry := 0.
+
+	done := false.
+	[done] whileFalse:[
+	    sum := carry.
+	    (index <= len1) ifTrue:[
+		sum := sum + (digitByteArray basicAt:index).
+		(index <= len2) ifTrue:[
+		    sum := sum + (otherDigitByteArray basicAt:index)
+		]
+	    ] ifFalse:[
+		(index <= len2) ifTrue:[
+		    sum := sum + (otherDigitByteArray basicAt:index)
+		] ifFalse:[
+		    "end reached"
+		    done := true
+		]
+	    ].
+	    (sum >= 16r100) ifTrue:[
+		carry := 1.
+		sum := sum - 16r100
+	    ] ifFalse:[
+		carry := 0
+	    ].
+	    resultDigitByteArray basicAt:index put:sum.
+	    index := index + 1
+	].
     ].
 
     ^ result compressed
@@ -5472,10 +5490,9 @@
 !LargeInteger class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/LargeInteger.st,v 1.226 2015-05-20 16:01:28 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/LargeInteger.st,v 1.226 2015-05-20 16:01:28 cg Exp $'
+    ^ '$Header$'
 ! !
-
--- a/Method.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/Method.st	Fri Jul 24 08:06:37 2015 +0100
@@ -2,7 +2,7 @@
 
 "
  COPYRIGHT (c) 1989 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
@@ -51,7 +51,7 @@
 copyright
 "
  COPYRIGHT (c) 1989 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
@@ -93,27 +93,27 @@
 
     [Instance variables:]
 
-        source          <String>        the source itself (if sourcePosition isNil)
-                                        or the fileName where the source is found
-
-        sourcePosition  <Integer>       the position of the methods chunk in the file
-
-        category        <Symbol>        the methods category
-        package         <Symbol>        the package, in which the methods was defined
-        mclass          <Class>         the class in which I am defined
-        indexed slots                   literals
+	source          <String>        the source itself (if sourcePosition isNil)
+					or the fileName where the source is found
+
+	sourcePosition  <Integer>       the position of the methods chunk in the file
+
+	category        <Symbol>        the methods category
+	package         <Symbol>        the package, in which the methods was defined
+	mclass          <Class>         the class in which I am defined
+	indexed slots                   literals
 
     [Class variables:]
 
-        PrivateMethodSignal             raised on privacy violation (see docu)
-
-        LastFileReference               weak reference to the last sourceFile
-        LastSourceFileName              to speedup source access via NFS
+	PrivateMethodSignal             raised on privacy violation (see docu)
+
+	LastFileReference               weak reference to the last sourceFile
+	LastSourceFileName              to speedup source access via NFS
 
     WARNING: layout known by compiler and runtime system - dont change
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 !
 
@@ -172,13 +172,13 @@
     Be warned and send me suggestions & critics (constructive ;-)
 
     Late note (Feb 2000):
-        the privacy feature has new been in ST/X for some years and was NOT heavily
-        used - neither at eXept, nor by customers.
-        In Smalltalk, it seems to be a very questionable feature, actually limiting
-        code reusability.
-        The privacy features are left in the system to demonstrate that it can be
-        done in Smalltalk (for religious C++ fans ... to avoid useless discussions)
-        (the check is not expensive, w.r.t. the VM runtime behavior).
+	the privacy feature has new been in ST/X for some years and was NOT heavily
+	used - neither at eXept, nor by customers.
+	In Smalltalk, it seems to be a very questionable feature, actually limiting
+	code reusability.
+	The privacy features are left in the system to demonstrate that it can be
+	done in Smalltalk (for religious C++ fans ... to avoid useless discussions)
+	(the check is not expensive, w.r.t. the VM runtime behavior).
 "
 ! !
 
@@ -188,18 +188,18 @@
     "create signals"
 
     PrivateMethodSignal isNil ifTrue:[
-        "EXPERIMENTAL"
-        PrivateMethodSignal := ExecutionError newSignalMayProceed:true.
-        PrivateMethodSignal nameClass:self message:#privateMethodSignal.
-        PrivateMethodSignal notifierString:'attempt to execute private/protected method'.
+	"EXPERIMENTAL"
+	PrivateMethodSignal := ExecutionError newSignalMayProceed:true.
+	PrivateMethodSignal nameClass:self message:#privateMethodSignal.
+	PrivateMethodSignal notifierString:'attempt to execute private/protected method'.
     ].
 
     LastFileLock isNil ifTrue:[
-        LastFileLock := RecursionLock new name:'Method-LastFile'.
-        LastMethodSourcesLock := RecursionLock new name:'Method-LastMethodSources'.
-
-        LastFileReference := WeakArray new:1.
-        LastFileReference at:1 put:nil.
+	LastFileLock := RecursionLock new name:'Method-LastFile'.
+	LastMethodSourcesLock := RecursionLock new name:'Method-LastMethodSources'.
+
+	LastFileReference := WeakArray new:1.
+	LastFileReference at:1 put:nil.
     ].
 
     CompilationLock := RecursionLock new name:'MethodCompilation'.
@@ -210,7 +210,7 @@
 
 lastMethodSourcesLock
     LastMethodSourcesLock isNil ifTrue:[
-        self initialize
+	self initialize
     ].
     ^ LastMethodSourcesLock
 ! !
@@ -258,10 +258,10 @@
     "
      in ST/X, binops are allowed with up-to 3 characters;
      for example:
-        <->
-        <=>
-        +++
-        :=:
+	<->
+	<=>
+	+++
+	:=:
      etc. are valid binOps here
     "
 !
@@ -269,8 +269,8 @@
 methodDefinitionTemplateForSelector:aSelector
     "given a selector, return a prototype definition string"
 
-    ^ self programmingLanguage 
-        methodDefinitionTemplateForSelector:aSelector
+    ^ self programmingLanguage
+	methodDefinitionTemplateForSelector:aSelector
 
     "
      Method methodDefinitionTemplateForSelector:#foo
@@ -282,11 +282,11 @@
 methodDefinitionTemplateForSelector:aSelector andArgumentNames:argNames
     "given a selector, return a prototype definition string"
 
-    ^ self programmingLanguage 
-        methodDefinitionTemplateForSelector:aSelector andArgumentNames:argNames
+    ^ self programmingLanguage
+	methodDefinitionTemplateForSelector:aSelector andArgumentNames:argNames
 
     "
-     Method methodDefinitionTemplateForSelector:#foo          andArgumentNames:#() 
+     Method methodDefinitionTemplateForSelector:#foo          andArgumentNames:#()
      Method methodDefinitionTemplateForSelector:#+            andArgumentNames:#('aNumber')
      Method methodDefinitionTemplateForSelector:#foo:bar:baz: andArgumentNames:#('fooArg' 'barArg' 'bazArg')
     "
@@ -327,8 +327,8 @@
 
 flushSourceStreamCache
     LastFileLock critical:[
-        LastSourceFileName := LastMethodSources := nil.
-        LastFileReference at:1 put:0.
+	LastSourceFileName := LastMethodSources := nil.
+	LastFileReference at:1 put:0.
     ].
 
     "
@@ -350,31 +350,31 @@
     |trapSel trapMethod|
 
     trapSel := #(
-                   invalidCodeObject
-                   invalidCodeObjectWith: 
-                   invalidCodeObjectWith:with: 
-                   invalidCodeObjectWith:with:with: 
-                   invalidCodeObjectWith:with:with:with: 
-                   invalidCodeObjectWith:with:with:with:with: 
-                   invalidCodeObjectWith:with:with:with:with:with: 
-                   invalidCodeObjectWith:with:with:with:with:with:with: 
-                   invalidCodeObjectWith:with:with:with:with:with:with:with: 
-                   invalidCodeObjectWith:with:with:with:with:with:with:with:with: 
-                   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with: 
-                   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with: 
-                   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with: 
-                   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with:with: 
-                   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with:with:with: 
-                   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with:with:with:with: 
-                ) at:(numArgs + 1).
+		   invalidCodeObject
+		   invalidCodeObjectWith:
+		   invalidCodeObjectWith:with:
+		   invalidCodeObjectWith:with:with:
+		   invalidCodeObjectWith:with:with:with:
+		   invalidCodeObjectWith:with:with:with:with:
+		   invalidCodeObjectWith:with:with:with:with:with:
+		   invalidCodeObjectWith:with:with:with:with:with:with:
+		   invalidCodeObjectWith:with:with:with:with:with:with:with:
+		   invalidCodeObjectWith:with:with:with:with:with:with:with:with:
+		   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:
+		   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:
+		   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with:
+		   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with:with:
+		   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with:with:with:
+		   invalidCodeObjectWith:with:with:with:with:with:with:with:with:with:with:with:with:with:with:
+		) at:(numArgs + 1).
 
     (trapMethod := self compiledMethodAt:trapSel) isNil ifTrue:[
-        trapMethod := Method compiledMethodAt:trapSel.
+	trapMethod := Method compiledMethodAt:trapSel.
     ].
     ^ trapMethod.
 
     "
-        self trapMethodForNumArgs:2
+	self trapMethodForNumArgs:2
     "
 
     "Created: / 04-11-1996 / 21:58:58 / cg"
@@ -423,19 +423,19 @@
 
     annots := self annotationsAt:aSymbol.
     annots isEmptyOrNil ifTrue:[
-        (aSymbol endsWith:$:) ifFalse:[
-            annots := self annotationsAt:(aSymbol,$:) asSymbol.
-        ].
-        annots isEmptyOrNil ifTrue:[
-            ^ exceptionValue value
-        ].
+	(aSymbol endsWith:$:) ifFalse:[
+	    annots := self annotationsAt:(aSymbol,$:) asSymbol.
+	].
+	annots isEmptyOrNil ifTrue:[
+	    ^ exceptionValue value
+	].
     ].
     ^ annots first arguments first
 !
 
 attributeMessages
-    ^ self annotations 
-        collect:[:annot | Message selector:annot key arguments:annot arguments]
+    ^ self annotations
+	collect:[:annot | Message selector:annot key arguments:annot arguments]
 !
 
 classIsMeta
@@ -473,18 +473,18 @@
     |newCategory oldCategory cls|
 
     aStringOrSymbol notNil ifTrue:[
-        newCategory := aStringOrSymbol.
-        newCategory ~= (oldCategory := category) ifTrue:[
-            self setCategory:newCategory.
-
-            cls := self mclass.
-            cls notNil ifTrue:[
-                cls addChangeRecordForMethodCategory:self category:newCategory.
-                self changed:#category with:oldCategory.            "/ will vanish
-                cls changed:#organization with:self selector.       "/ will vanish
-                Smalltalk changed:#methodCategory with:(Array with:cls with:self with:oldCategory).
-            ]
-        ]
+	newCategory := aStringOrSymbol.
+	newCategory ~= (oldCategory := category) ifTrue:[
+	    self setCategory:newCategory.
+
+	    cls := self mclass.
+	    cls notNil ifTrue:[
+		cls addChangeRecordForMethodCategory:self category:newCategory.
+		self changed:#category with:oldCategory.            "/ will vanish
+		cls changed:#organization with:self selector.       "/ will vanish
+		Smalltalk changed:#methodCategory with:(Array with:cls with:self with:oldCategory).
+	    ]
+	]
     ]
 
     "Modified: / 25-09-2007 / 16:15:24 / cg"
@@ -518,7 +518,7 @@
      due to an accept in a browser or debugger. However, the mclass slot still contains a
      reference to the once valid class"
 
-    ^ mclass 
+    ^ mclass
 !
 
 getPackage
@@ -566,9 +566,9 @@
 
 lookupObject: anObject
     anObject == BuiltinLookup instance ifTrue:[
-        self setLookupObject: nil
+	self setLookupObject: nil
     ] ifFalse:[
-        self setLookupObject: anObject.
+	self setLookupObject: anObject.
     ].
 
     "Created: / 28-04-2010 / 18:36:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -583,12 +583,12 @@
      sourceCode is not lost."
 
     source notNil ifTrue:[
-        sourcePosition notNil ifTrue:[
-            "/ this looks wierd - but (self source) will retrieve the external source
-            "/ (from the file) and store it. So afterwards, we will have the string and
-            "/ sourcePosition will be nil
-            self source:(self source)
-        ]
+	sourcePosition notNil ifTrue:[
+	    "/ this looks wierd - but (self source) will retrieve the external source
+	    "/ (from the file) and store it. So afterwards, we will have the string and
+	    "/ sourcePosition will be nil
+	    self source:(self source)
+	]
     ].
 !
 
@@ -684,7 +684,7 @@
 
     Overrides isNil ifTrue:[^ nil].
     ^ (Overrides includesKey: self)
-        ifTrue:[Overrides at: self]
+	ifTrue:[Overrides at: self]
 
     "Created: / 05-07-2012 / 10:49:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -709,12 +709,12 @@
 
     "/ get it from my class
     (cls := self mclass) isNil ifTrue:[
-        ^ PackageId noProjectID.
+	^ PackageId noProjectID.
     ].
     "/ set it.
     package := cls getPackage.
     package isNil ifTrue:[
-        ^ PackageId noProjectID.
+	^ PackageId noProjectID.
     ].
     ^ package
 
@@ -727,36 +727,36 @@
     |cls oldPackage newPackage|
 
     aSymbol == PackageId noProjectID ifTrue:[
-        newPackage := nil
+	newPackage := nil
     ] ifFalse:[
-        newPackage := aSymbol
+	newPackage := aSymbol
     ].
 
     package ~~ newPackage ifTrue:[
-        oldPackage := package.
-        "/ this is required, because otherwise I would no longer be able to
-        "/ reconstruct my sourcecode (as the connection to the source-file is lost).
-        self makeLocalStringSource.
-        package := newPackage.
-
-        cls := self mclass.
-        "JV@2011-01-27: BUG FIX: method may be wrapped (breakpoint on it). 
-         Search for the wrapper, if none is found, return immediately
-         (avoids DNU)"
-        cls isNil ifTrue:[
-            | wrapper |
-
-            wrapper := self wrapper.
-            wrapper isNil ifTrue:[ ^ self ].
-            cls := wrapper mclass.
-            cls isNil ifTrue:[ ^ self ].
-        ].
-
-        self changed:#package.                                              "/ will vanish
-        cls changed:#methodPackage with:self selector.                      "/ will vanish
-
-        Smalltalk changed:#projectOrganization with:(Array with:cls with:self with:oldPackage).
-        cls addChangeRecordForMethodPackage:self package:newPackage.
+	oldPackage := package.
+	"/ this is required, because otherwise I would no longer be able to
+	"/ reconstruct my sourcecode (as the connection to the source-file is lost).
+	self makeLocalStringSource.
+	package := newPackage.
+
+	cls := self mclass.
+	"JV@2011-01-27: BUG FIX: method may be wrapped (breakpoint on it).
+	 Search for the wrapper, if none is found, return immediately
+	 (avoids DNU)"
+	cls isNil ifTrue:[
+	    | wrapper |
+
+	    wrapper := self wrapper.
+	    wrapper isNil ifTrue:[ ^ self ].
+	    cls := wrapper mclass.
+	    cls isNil ifTrue:[ ^ self ].
+	].
+
+	self changed:#package.                                              "/ will vanish
+	cls changed:#methodPackage with:self selector.                      "/ will vanish
+
+	Smalltalk changed:#projectOrganization with:(Array with:cls with:self with:oldPackage).
+	cls addChangeRecordForMethodPackage:self package:newPackage.
     ]
 
     "Modified: / 23-11-2006 / 17:01:02 / cg"
@@ -776,7 +776,7 @@
     "set the methods category (without change notification)"
 
     aStringOrSymbol notNil ifTrue:[
-        category := aStringOrSymbol asSymbol
+	category := aStringOrSymbol asSymbol
     ]
 
     "Modified: / 13.11.1998 / 23:55:05 / cg"
@@ -802,75 +802,75 @@
     source isNil ifTrue:[^ nil].
 
     self class lastMethodSourcesLock critical:[
-        LastMethodSources notNil ifTrue:[
-            chunk := LastMethodSources at:self ifAbsent:nil.
-        ].
+	LastMethodSources notNil ifTrue:[
+	    chunk := LastMethodSources at:self ifAbsent:nil.
+	].
     ].
     chunk notNil ifTrue:[
-        ^ chunk
+	^ chunk
     ].
 
     LastFileLock
-        critical:[
-            "have to protect sourceStream from being closed as a side effect
-             of some other process fetching some the source from a different source file"
-
-            sourceStream := self sourceStreamUsingCache:true.
-            sourceStream notNil ifTrue:[
-                [
-                    chunk := self sourceChunkFromStream:sourceStream.
-                ] on:DecodingError do:[:ex|
-                    "CharacterEncoder>>#guessEncoding is not fail safe - retry with plain unencoded data"
-
-                    ('DecodingError ignored when reading <1p> (<2p>)' expandMacrosWith:self whoString with:ex description) infoPrintCR.
-                    sourceStream := self rawSourceStreamUsingCache:true.
-                    ex restart.
-                ].
-            ].
-        ]
-        timeoutMs:100
-        ifBlocking:[
-            "take care if LastFileLock is not available - maybe we are
-             called by a debugger while someone holds the lock.
-             Use uncached source streams"
-            sourceStream := self sourceStreamUsingCache:false.
-            sourceStream notNil ifTrue:[
-                [
-                    chunk := self sourceChunkFromStream:sourceStream.
-                    sourceStream close.
-                ] on:DecodingError do:[:ex|
-                    "CharacterEncoder>>#guessEncoding is not fail safe - retry with plain unencoded data"
-                    ('DecodingError ignored when reading <1p> (<2p>)' expandMacrosWith:self whoString with:ex description) infoPrintCR.
-                    sourceStream close.
-                    sourceStream := self rawSourceStreamUsingCache:false.
-                    ex restart.
-                ].
-            ].
-        ].
+	critical:[
+	    "have to protect sourceStream from being closed as a side effect
+	     of some other process fetching some the source from a different source file"
+
+	    sourceStream := self sourceStreamUsingCache:true.
+	    sourceStream notNil ifTrue:[
+		[
+		    chunk := self sourceChunkFromStream:sourceStream.
+		] on:DecodingError do:[:ex|
+		    "CharacterEncoder>>#guessEncoding is not fail safe - retry with plain unencoded data"
+
+		    ('DecodingError ignored when reading <1p> (<2p>)' expandMacrosWith:self whoString with:ex description) infoPrintCR.
+		    sourceStream := self rawSourceStreamUsingCache:true.
+		    ex restart.
+		].
+	    ].
+	]
+	timeoutMs:100
+	ifBlocking:[
+	    "take care if LastFileLock is not available - maybe we are
+	     called by a debugger while someone holds the lock.
+	     Use uncached source streams"
+	    sourceStream := self sourceStreamUsingCache:false.
+	    sourceStream notNil ifTrue:[
+		[
+		    chunk := self sourceChunkFromStream:sourceStream.
+		    sourceStream close.
+		] on:DecodingError do:[:ex|
+		    "CharacterEncoder>>#guessEncoding is not fail safe - retry with plain unencoded data"
+		    ('DecodingError ignored when reading <1p> (<2p>)' expandMacrosWith:self whoString with:ex description) infoPrintCR.
+		    sourceStream close.
+		    sourceStream := self rawSourceStreamUsingCache:false.
+		    ex restart.
+		].
+	    ].
+	].
 
     "Cache the source of recently used methods"
     chunk notNil ifTrue:[
-        "JV@2013-08-19: Don't consult UserPreferences if the system is initilizing. This may
-         lead in funny side-effect as #initializeDefaultPreferences is called which tries to
-         initialize some colors. But Color itsels is likely not yet initialized, so DNU is 
-         thrown.
-         CG: also care for standalone non-GUI progs, which have no userPreferences class"
-        (Smalltalk isInitialized 
-        and:[UserPreferences notNil
-        and:[UserPreferences current keepMethodSourceCode]]) ifTrue:[
-            source := chunk.
-            sourcePosition := nil.
-            ^ source.
-        ].
-
-        CacheDictionary notNil ifTrue:[
-            self class lastMethodSourcesLock critical:[
-                LastMethodSources isNil ifTrue:[
-                    LastMethodSources := CacheDictionary new:50.
-                ].
-                LastMethodSources at:self put:chunk.
-            ]
-        ].
+	"JV@2013-08-19: Don't consult UserPreferences if the system is initilizing. This may
+	 lead in funny side-effect as #initializeDefaultPreferences is called which tries to
+	 initialize some colors. But Color itsels is likely not yet initialized, so DNU is
+	 thrown.
+	 CG: also care for standalone non-GUI progs, which have no userPreferences class"
+	(Smalltalk isInitialized
+	and:[UserPreferences notNil
+	and:[UserPreferences current keepMethodSourceCode]]) ifTrue:[
+	    source := chunk.
+	    sourcePosition := nil.
+	    ^ source.
+	].
+
+	CacheDictionary notNil ifTrue:[
+	    self class lastMethodSourcesLock critical:[
+		LastMethodSources isNil ifTrue:[
+		    LastMethodSources := CacheDictionary new:50.
+		].
+		LastMethodSources at:self put:chunk.
+	    ]
+	].
     ].
 
     ^ chunk
@@ -931,18 +931,18 @@
 
     index := self annotationIndexOf: annotation key.
     index isNil ifTrue:[
-        annotations := annotations isNil 
-                            ifTrue:[Array with: annotation]
-                            ifFalse:[annotations copyWith:annotation]
+	annotations := annotations isNil
+			    ifTrue:[Array with: annotation]
+			    ifFalse:[annotations copyWith:annotation]
     ] ifFalse:[
-        annotations at: index put: annotation
+	annotations at: index put: annotation
     ].
 "/    annotation annotatesMethod: self.
 
     "
-        (Object >> #yourself) annotateWith: (Annotation namespace: 'Fictious').
-        (Object >> #yourself) annotations.
-        (Object >> #yourself) annotationAt: #namespace:
+	(Object >> #yourself) annotateWith: (Annotation namespace: 'Fictious').
+	(Object >> #yourself) annotations.
+	(Object >> #yourself) annotationAt: #namespace:
     "
 
     "Created: / 19-05-2010 / 16:20:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -958,7 +958,7 @@
     ^ self annotationAtIndex: index.
 
     "
-        (Object >> #yourself) annotationAt: #namespace:
+	(Object >> #yourself) annotationAt: #namespace:
     "
 
     "Created: / 19-05-2010 / 16:16:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -976,7 +976,7 @@
 
     retval := Array new: annotations size.
     1 to: annotations size do: [:i|
-        retval at: i put: (self annotationAtIndex: i).
+	retval at: i put: (self annotationAtIndex: i).
     ].
     ^ retval.
 
@@ -999,10 +999,10 @@
 
 annotationsAt: key
 
-    ^OrderedCollection 
-        streamContents:[:annotStream|
-            self annotationsAt: key do: [:annot| annotStream nextPut: annot]
-        ]
+    ^OrderedCollection
+	streamContents:[:annotStream|
+	    self annotationsAt: key do: [:annot| annotStream nextPut: annot]
+	]
 
     "Created: / 16-07-2010 / 11:41:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified (format): / 26-07-2012 / 15:46:56 / cg"
@@ -1010,7 +1010,7 @@
 
 annotationsAt: key do: block
     self annotationsDo: [:annot|
-        annot key == key ifTrue:[block value: annot]
+	annot key == key ifTrue:[block value: annot]
     ]
 
     "Created: / 16-07-2010 / 11:48:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1019,10 +1019,10 @@
 
 annotationsAt: key1 orAt: key2
 
-    ^OrderedCollection 
-        streamContents:[:annotStream|
-            self annotationsAt: key1 orAt: key2 do: [:annot|annotStream nextPut: annot]
-        ]
+    ^OrderedCollection
+	streamContents:[:annotStream|
+	    self annotationsAt: key1 orAt: key2 do: [:annot|annotStream nextPut: annot]
+	]
 
     "Created: / 16-07-2010 / 11:41:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified (format): / 26-07-2012 / 15:49:11 / cg"
@@ -1030,9 +1030,9 @@
 
 annotationsAt: key1 orAt: key2 do: block
     self annotationsDo:[:annot |
-        (annot key == key1 or:[annot key == key2]) ifTrue:[
-            block value: annot
-        ]
+	(annot key == key1 or:[annot key == key2]) ifTrue:[
+	    block value: annot
+	]
     ]
 
     "Created: / 16-07-2010 / 11:47:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1042,7 +1042,7 @@
 annotationsDo: aBlock
     annotations isNil ifTrue:[^nil].
     1 to: annotations size do: [:i|
-        aBlock value: (self annotationAtIndex: i)
+	aBlock value: (self annotationAtIndex: i)
     ].
 
     "Created: / 02-07-2010 / 22:33:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1139,7 +1139,7 @@
     INT f = __intVal(__INST(flags));
 
     if (f & F_RESTRICTED) {
-        RETURN (true);
+	RETURN (true);
     }
 #endif
 %}.
@@ -1170,15 +1170,15 @@
     INT p;
 
     if (aSymbol == @symbol(public))
-        p = 0;
+	p = 0;
     else if (aSymbol == @symbol(protected))
-        p = F_PRIVATE;
+	p = F_PRIVATE;
     else if (aSymbol == @symbol(private))
-        p = F_CLASSPRIVATE;
+	p = F_CLASSPRIVATE;
     else if (aSymbol == @symbol(ignored))
-        p = F_IGNORED;
+	p = F_IGNORED;
     else
-        RETURN(false);  /* illegal symbol */
+	RETURN(false);  /* illegal symbol */
 
 
     f = (f & ~M_PRIVACY) | p;
@@ -1216,18 +1216,18 @@
 
 # ifdef F_PRIVATE
     case F_PRIVATE:
-        RETURN (@symbol(protected));
-        break;
+	RETURN (@symbol(protected));
+	break;
 # endif
 # ifdef F_CLASSPRIVATE
     case F_CLASSPRIVATE:
-        RETURN (@symbol(private));
-        break;
+	RETURN (@symbol(private));
+	break;
 # endif
 # ifdef F_IGNORED
     case F_IGNORED:
-        RETURN (@symbol(ignored));
-        break;
+	RETURN (@symbol(ignored));
+	break;
 # endif
     }
 #endif
@@ -1254,19 +1254,19 @@
     oldPrivacy := self privacy.
 
     (self setPrivacy:aSymbol flushCaches:true) ifTrue:[
-        |myClass mySelector|
-
-        myClass := self mclass.
-        mySelector := self selector.
-
-        self changed:#privacy.                                       "/ will vanish
-        myClass notNil ifTrue:[
-            mySelector notNil ifTrue:[
-                myClass changed:#methodPrivacy with:mySelector.      "/ will vanish
-                Smalltalk changed:#privacyOfMethod with:(Array with:myClass with:self with:oldPrivacy).
-                myClass addChangeRecordForMethodPrivacy:self.
-            ]
-        ]
+	|myClass mySelector|
+
+	myClass := self mclass.
+	mySelector := self selector.
+
+	self changed:#privacy.                                       "/ will vanish
+	myClass notNil ifTrue:[
+	    mySelector notNil ifTrue:[
+		myClass changed:#methodPrivacy with:mySelector.      "/ will vanish
+		Smalltalk changed:#privacyOfMethod with:(Array with:myClass with:self with:oldPrivacy).
+		myClass addChangeRecordForMethodPrivacy:self.
+	    ]
+	]
     ]
 
     "Modified: / 23-11-2006 / 17:03:20 / cg"
@@ -1293,12 +1293,12 @@
 
     old = f;
     if (aBoolean == true)
-        f |= F_RESTRICTED;
+	f |= F_RESTRICTED;
     else
-        f &= ~F_RESTRICTED;
+	f &= ~F_RESTRICTED;
     __INST(flags) = __mkSmallInteger(f);
     if (old & F_RESTRICTED)
-        RETURN(true);
+	RETURN(true);
 #endif
 %}.
     ^ false
@@ -1353,13 +1353,13 @@
     "/ no need to flush, if changing from private to public
     "/
     doFlush ifTrue:[
-        (aSymbol == #public and:[old ~~ #ignored]) ifFalse:[
-            (sel := self selector) notNil ifTrue:[
-                ObjectMemory flushCachesForSelector:sel numArgs:self argumentCount
-            ] ifFalse:[
-                ObjectMemory flushCaches.
-            ].
-        ].
+	(aSymbol == #public and:[old ~~ #ignored]) ifFalse:[
+	    (sel := self selector) notNil ifTrue:[
+		ObjectMemory flushCachesForSelector:sel numArgs:self argumentCount
+	    ] ifFalse:[
+		ObjectMemory flushCaches.
+	    ].
+	].
     ].
     ^ true
 ! !
@@ -1380,17 +1380,17 @@
     |mthd|
 
     byteCode notNil ifTrue:[
-        "
-         is already a bytecoded method
-        "
-        ^ self
+	"
+	 is already a bytecoded method
+	"
+	^ self
     ].
 
     ParserFlags
-        withSTCCompilation:#never
-        do:[
-            mthd := self asExecutableMethod.
-        ].
+	withSTCCompilation:#never
+	do:[
+	    mthd := self asExecutableMethod.
+	].
     ^ mthd
 
     "Created: 24.10.1995 / 14:02:32 / cg"
@@ -1401,10 +1401,10 @@
     |mthd|
 
     ParserFlags
-        withSTCCompilation:#never
-        do:[
-            mthd := self asExecutableMethodWithSource:newSource.
-        ].
+	withSTCCompilation:#never
+	do:[
+	    mthd := self asExecutableMethodWithSource:newSource.
+	].
     ^ mthd
 
     "Created: 24.10.1995 / 14:02:32 / cg"
@@ -1423,23 +1423,23 @@
     |temporaryMethod sourceString|
 
     byteCode notNil ifTrue:[
-        "
-         is already a bytecoded method
-        "
-        ^ self
+	"
+	 is already a bytecoded method
+	"
+	^ self
     ].
 
     sourceString := self source.
     sourceString isNil ifTrue:[
-        'Method [warning]: cannot generate bytecode (no source for compilation)' errorPrintCR.
-        ^ nil
+	'Method [warning]: cannot generate bytecode (no source for compilation)' errorPrintCR.
+	^ nil
     ].
 
     temporaryMethod := self asExecutableMethodWithSource:sourceString.
 
     (temporaryMethod isNil or:[temporaryMethod == #Error]) ifTrue:[
-        'Method [warning]: cannot generate bytecode (contains primitive code or error)' errorPrintCR.
-        ^ nil.
+	'Method [warning]: cannot generate bytecode (contains primitive code or error)' errorPrintCR.
+	^ nil.
     ].
     "/
     "/ try to save a bit of memory, by sharing the source (whatever it is)
@@ -1453,8 +1453,8 @@
 
     cls := self containingClass.
     cls isNil ifTrue:[
-        'Method [warning]: cannot generate bytecode (no class for compilation)' errorPrintCR.
-        ^ nil
+	'Method [warning]: cannot generate bytecode (no class for compilation)' errorPrintCR.
+	^ nil
     ].
 
     "we have to sequentialize this using a lock-semaphore,
@@ -1464,53 +1464,53 @@
      (happened when autoloading animation demos)
     "
     CompilationLock critical:[
-        "
-         dont want this to go into the changes file,
-         dont want output on Transcript and definitely
-         dont want a lazy method ...
-        "
-        Class withoutUpdatingChangesDo:[
-            |silent lazy|
-
-            silent := Smalltalk silentLoading:true.
-            lazy := Compiler compileLazy:false.
-
-            [
-                |compiler|
-
-                Class nameSpaceQuerySignal answer:(cls nameSpace)
-                do:[
-                    compiler := cls compilerClass.
-
-                    "/
-                    "/ kludge - have to make ST/X's compiler protocol
-                    "/ be compatible to ST-80's
-                    "/
-                    (compiler respondsTo:#compile:forClass:inCategory:notifying:install:)
-                    ifTrue:[
-                        temporaryMethod := compiler
-                                             compile:newSource
-                                             forClass:cls
-                                             inCategory:(self category)
-                                             notifying:nil
-                                             install:false.
-                    ] ifFalse:[
-                        temporaryMethod := compiler new
-                                             compile:newSource
-                                             in:cls
-                                             notifying:nil
-                                             ifFail:nil
-                    ].
-                ].
-            ] ensure:[
-                Compiler compileLazy:lazy.
-                Smalltalk silentLoading:silent.
-            ]
-        ].
+	"
+	 dont want this to go into the changes file,
+	 dont want output on Transcript and definitely
+	 dont want a lazy method ...
+	"
+	Class withoutUpdatingChangesDo:[
+	    |silent lazy|
+
+	    silent := Smalltalk silentLoading:true.
+	    lazy := Compiler compileLazy:false.
+
+	    [
+		|compiler|
+
+		Class nameSpaceQuerySignal answer:(cls nameSpace)
+		do:[
+		    compiler := cls compilerClass.
+
+		    "/
+		    "/ kludge - have to make ST/X's compiler protocol
+		    "/ be compatible to ST-80's
+		    "/
+		    (compiler respondsTo:#compile:forClass:inCategory:notifying:install:)
+		    ifTrue:[
+			temporaryMethod := compiler
+					     compile:newSource
+					     forClass:cls
+					     inCategory:(self category)
+					     notifying:nil
+					     install:false.
+		    ] ifFalse:[
+			temporaryMethod := compiler new
+					     compile:newSource
+					     in:cls
+					     notifying:nil
+					     ifFail:nil
+		    ].
+		].
+	    ] ensure:[
+		Compiler compileLazy:lazy.
+		Smalltalk silentLoading:silent.
+	    ]
+	].
     ].
     (temporaryMethod isNil or:[temporaryMethod == #Error]) ifTrue:[
-        'Method [warning]: cannot generate bytecode (contains primitive code or error)' errorPrintCR.
-        ^ nil.
+	'Method [warning]: cannot generate bytecode (contains primitive code or error)' errorPrintCR.
+	^ nil.
     ].
     "/
     "/ try to save a bit of memory, by sharing the source (whatever it is)
@@ -1533,7 +1533,7 @@
 
     aCopy := super copy.
     sourcePosition notNil ifTrue:[
-        aCopy source:(self source)
+	aCopy source:(self source)
     ].
     aCopy mclass:nil.
     ^ aCopy
@@ -1566,7 +1566,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Modified: 4.11.1996 / 22:45:06 / cg"
 !
@@ -1585,7 +1585,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: / 14-09-2011 / 11:23:49 / sr"
 !
@@ -1604,7 +1604,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:16:41 / cg"
     "Modified: 4.11.1996 / 22:45:15 / cg"
@@ -1624,7 +1624,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:16:51 / cg"
     "Modified: 4.11.1996 / 22:45:18 / cg"
@@ -1644,7 +1644,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:00 / cg"
     "Modified: 4.11.1996 / 22:45:22 / cg"
@@ -1664,7 +1664,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:09 / cg"
     "Modified: 4.11.1996 / 22:45:25 / cg"
@@ -1684,7 +1684,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:17 / cg"
     "Modified: 4.11.1996 / 22:45:28 / cg"
@@ -1704,7 +1704,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:25 / cg"
     "Modified: 4.11.1996 / 22:45:31 / cg"
@@ -1724,7 +1724,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:32 / cg"
     "Modified: 4.11.1996 / 22:45:38 / cg"
@@ -1744,7 +1744,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:37 / cg"
     "Modified: 4.11.1996 / 22:45:41 / cg"
@@ -1764,7 +1764,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:45 / cg"
     "Modified: 4.11.1996 / 22:45:44 / cg"
@@ -1784,7 +1784,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:17:52 / cg"
     "Modified: 4.11.1996 / 22:45:47 / cg"
@@ -1804,7 +1804,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 20:51:28 / cg"
     "Modified: 4.11.1996 / 22:46:01 / cg"
@@ -1824,7 +1824,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:18:09 / cg"
     "Modified: 4.11.1996 / 22:45:57 / cg"
@@ -1844,7 +1844,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:18:17 / cg"
     "Modified: 4.11.1996 / 22:45:55 / cg"
@@ -1864,7 +1864,7 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseErrorString:'invalid method - not executable'.
+	raiseErrorString:'invalid method - not executable'.
 
     "Created: 4.11.1996 / 21:18:22 / cg"
     "Modified: 4.11.1996 / 22:45:52 / cg"
@@ -1913,8 +1913,8 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseRequestWith:self
-        errorString:'invalid method - not compiled'.
+	raiseRequestWith:self
+	errorString:'invalid method - not compiled'.
 
     "Modified: 4.11.1996 / 22:58:02 / cg"
 !
@@ -1933,8 +1933,8 @@
      */
 %}.
     ^ InvalidCodeError
-        raiseRequestWith:self
-        errorString:'invalid method - unloaded'.
+	raiseRequestWith:self
+	errorString:'invalid method - unloaded'.
 
     "Created: 4.11.1996 / 22:57:54 / cg"
     "Modified: 4.11.1996 / 22:58:28 / cg"
@@ -1957,30 +1957,30 @@
 
     classAndSelector := self who.
     classAndSelector isNil ifTrue:[
-        "
-         not anchored in any class.
-         check if wrapped (to be more informative in inspectors)
-        "
-        m := self wrapper.
-        m notNil ifTrue:[
-            classAndSelector := m who.
-            wrapped := true.
-        ]
+	"
+	 not anchored in any class.
+	 check if wrapped (to be more informative in inspectors)
+	"
+	m := self wrapper.
+	m notNil ifTrue:[
+	    classAndSelector := m who.
+	    wrapped := true.
+	]
     ].
     classAndSelector notNil ifTrue:[
-        (classAndSelector methodClass) name printOn:aStream.
-        aStream nextPutAll:' '.
-        (classAndSelector methodSelector) printOn:aStream.
+	(classAndSelector methodClass) name printOn:aStream.
+	aStream nextPutAll:' '.
+	(classAndSelector methodSelector) printOn:aStream.
     ] ifFalse:[
-        "
-         sorry, a method which is nowhere anchored
-        "
-        aStream nextPutAll:'unbound'
+	"
+	 sorry, a method which is nowhere anchored
+	"
+	aStream nextPutAll:'unbound'
     ].
     aStream nextPut:$).
 
     wrapped ifTrue:[
-        aStream nextPutAll:'; wrapped'
+	aStream nextPutAll:'; wrapped'
     ].
 
     "
@@ -2002,7 +2002,7 @@
 
     who := self who.
     who notNil ifTrue:[
-        ^ who methodClass name , ' >> ' , (who methodSelector storeString)
+	^ who methodClass name , ' >> ' , (who methodSelector storeString)
     ].
     ^ 'unboundMethod'
 
@@ -2028,21 +2028,21 @@
 
     annotationOrArray := annotation := annotations at: index.
     annotationOrArray isArray ifTrue:[
-        args := annotationOrArray size == 2
-                    ifTrue:[annotationOrArray second]
-                    ifFalse:[#()].
-        args isArray ifFalse:[args := Array with: args].
-        annotation := Annotation
-                        method:self
-                        key: annotationOrArray first
-                        arguments: args.
-        annotation isUnknown ifFalse:[
-            annotations isImmutable ifTrue:[
-                annotations := annotations asArray
-            ].
-            annotations at: index put: annotation.
+	args := annotationOrArray size == 2
+		    ifTrue:[annotationOrArray second]
+		    ifFalse:[#()].
+	args isArray ifFalse:[args := Array with: args].
+	annotation := Annotation
+			method:self
+			key: annotationOrArray first
+			arguments: args.
+	annotation isUnknown ifFalse:[
+	    annotations isImmutable ifTrue:[
+		annotations := annotations asArray
+	    ].
+	    annotations at: index put: annotation.
 "/            annotation annotatesMethod: self
-        ].
+	].
     ].
     ^annotation
 
@@ -2059,9 +2059,9 @@
     annotations isNil ifTrue:[^nil].
 
     annotations keysAndValuesDo: [:index :annotationOrArray|
-        annotationOrArray isArray
-            ifTrue: [annotationOrArray first == key ifTrue:[^index]]
-            ifFalse:[annotationOrArray key == key ifTrue:[^index]]
+	annotationOrArray isArray
+	    ifTrue: [annotationOrArray first == key ifTrue:[^index]]
+	    ifFalse:[annotationOrArray key == key ifTrue:[^index]]
     ].
     ^nil.
 
@@ -2076,14 +2076,16 @@
     |lastStream|
 
     (package notNil and:[package ~= PackageId noProjectID]) ifTrue:[
-        LastFileLock critical:[
-            lastStream := LastFileReference at:1.
-            (lastStream notNil and:[lastStream ~= 0 and:[lastStream isOpen]]) ifTrue:[
-                lastStream close.
-            ].
-            LastSourceFileName := package,'/',source.
-            LastFileReference at:1 put:aStream.
-        ].
+	LastFileLock critical:[
+	    lastStream := LastFileReference at:1.
+	    (lastStream notNil
+	      and:[lastStream class ~~ SmallInteger
+	      and:[lastStream isOpen]]) ifTrue:[
+		lastStream close.
+	    ].
+	    LastSourceFileName := package,'/',source.
+	    LastFileReference at:1 put:aStream.
+	].
     ].
 !
 
@@ -2109,29 +2111,29 @@
     |dir fileName aStream|
 
     package notNil ifTrue:[
-        "/
-        "/ old: look in 'source/<filename>'
-        "/ this is still kept in order to find user-private
-        "/ classes in her currentDirectory.
-        "/
-        fileName := Smalltalk getSourceFileName:(package copyReplaceAll:$: with:$/) , '/' , source.
-        fileName notNil ifTrue:[
-            aStream := fileName asFilename readStreamOrNil.
-            aStream notNil ifTrue:[^ aStream].
-        ].
-        "/
-        "/ new: look in package-dir
-        "/
-        dir := Smalltalk getPackageDirectoryForPackage:package.
-        dir notNil ifTrue:[
-            fileName := dir construct:source.
-            aStream := fileName asFilename readStreamOrNil.
-            aStream notNil ifTrue:[^ aStream].
-        ].
+	"/
+	"/ old: look in 'source/<filename>'
+	"/ this is still kept in order to find user-private
+	"/ classes in her currentDirectory.
+	"/
+	fileName := Smalltalk getSourceFileName:(package copyReplaceAll:$: with:$/) , '/' , source.
+	fileName notNil ifTrue:[
+	    aStream := fileName asFilename readStreamOrNil.
+	    aStream notNil ifTrue:[^ aStream].
+	].
+	"/
+	"/ new: look in package-dir
+	"/
+	dir := Smalltalk getPackageDirectoryForPackage:package.
+	dir notNil ifTrue:[
+	    fileName := dir construct:source.
+	    aStream := fileName asFilename readStreamOrNil.
+	    aStream notNil ifTrue:[^ aStream].
+	].
     ].
     fileName := Smalltalk getSourceFileName:source.
     fileName notNil ifTrue:[
-        aStream := fileName asFilename readStreamOrNil.
+	aStream := fileName asFilename readStreamOrNil.
     ].
     ^ aStream
 !
@@ -2153,28 +2155,30 @@
     sourcePosition isNil ifTrue:[^ source readStream].
 
     usingCacheBoolean ifTrue:[
-        (package notNil and:[package ~= PackageId noProjectID]) ifTrue:[
-            "/ keep the last source file open, because open/close
-            "/ operations maybe slow on NFS-mounted file systems.
-            "/ Since the reference to the file is weak, it will be closed
-            "/ automatically if the file is not referenced for a while.
-            "/ Neat trick.
-
-            LastFileLock critical:[
-                aStream := LastFileReference at:1.
-                (aStream isNil or:[aStream == 0 or:[aStream isOpen not]]) ifTrue:[
-                    aStream := nil.
-                    LastFileReference at:1 put:nil.
-                ].
-                (aStream notNil and:[LastSourceFileName ~= (package,'/',source)]) ifTrue:[
-                    aStream := nil.
-                ].
-            ].
-
-            aStream notNil ifTrue:[
-                ^ aStream
-            ].
-        ].
+	(package notNil and:[package ~= PackageId noProjectID]) ifTrue:[
+	    "/ keep the last source file open, because open/close
+	    "/ operations maybe slow on NFS-mounted file systems.
+	    "/ Since the reference to the file is weak, it will be closed
+	    "/ automatically if the file is not referenced for a while.
+	    "/ Neat trick.
+
+	    LastFileLock critical:[
+		aStream := LastFileReference at:1.
+		(aStream isNil
+		  or:[aStream class == SmallInteger
+		  or:[aStream isOpen not]]) ifTrue:[
+		    aStream := nil.
+		    LastFileReference at:1 put:nil.
+		].
+		(aStream notNil and:[LastSourceFileName ~= (package,'/',source)]) ifTrue:[
+		    aStream := nil.
+		].
+	    ].
+
+	    aStream notNil ifTrue:[
+		^ aStream
+	    ].
+	].
     ].
 
     "/ a negative sourcePosition indicates
@@ -2185,47 +2189,47 @@
     "/ and having a clue for which file is meant later.
 
     sourcePosition < 0 ifTrue:[
-        aStream := source asFilename readStreamOrNil.
-        aStream isNil ifTrue:[
-            "/ search in some standard places
-            fileName := Smalltalk getSourceFileName:source.
-            fileName notNil ifTrue:[
-                aStream := fileName asFilename readStreamOrNil.
-            ].
-        ].
-        aStream notNil ifTrue:[
-            usingCacheBoolean ifTrue:[
-                self cacheSourceStream:aStream.
-            ].
-            ^ aStream
-        ].
+	aStream := source asFilename readStreamOrNil.
+	aStream isNil ifTrue:[
+	    "/ search in some standard places
+	    fileName := Smalltalk getSourceFileName:source.
+	    fileName notNil ifTrue:[
+		aStream := fileName asFilename readStreamOrNil.
+	    ].
+	].
+	aStream notNil ifTrue:[
+	    usingCacheBoolean ifTrue:[
+		self cacheSourceStream:aStream.
+	    ].
+	    ^ aStream
+	].
     ].
 
     "/
     "/ if there is no SourceManager, look in local standard places first
     "/
     (mclass notNil and:[package == mclass package]) ifTrue:[
-        mgr := mclass sourceCodeManagerFromBinaryRevision
+	mgr := mclass sourceCodeManagerFromBinaryRevision
     ] ifFalse:[
-        "I'm an extension and we don't have binary revision info (!!)
-         for extensions, try to guess here"
-        pkgDef := ProjectDefinition definitionClassForPackage: package.
-        pkgDef notNil ifTrue:[
-            mgr := pkgDef sourceCodeManagerFromBinaryRevision
-        ] ifFalse:[
-            "OK, trust the configuration"
-            mgr := AbstractSourceCodeManager managerForPackage: package
-        ]
+	"I'm an extension and we don't have binary revision info (!!)
+	 for extensions, try to guess here"
+	pkgDef := ProjectDefinition definitionClassForPackage: package.
+	pkgDef notNil ifTrue:[
+	    mgr := pkgDef sourceCodeManagerFromBinaryRevision
+	] ifFalse:[
+	    "OK, trust the configuration"
+	    mgr := AbstractSourceCodeManager managerForPackage: package
+	]
     ].
 
     (Class tryLocalSourceFirst or:[mgr isNil]) ifTrue:[
-        aStream := self localSourceStream.
-        aStream notNil ifTrue:[
-            usingCacheBoolean ifTrue:[
-                self cacheSourceStream:aStream.
-            ].
-            ^ aStream
-        ].
+	aStream := self localSourceStream.
+	aStream notNil ifTrue:[
+	    usingCacheBoolean ifTrue:[
+		self cacheSourceStream:aStream.
+	    ].
+	    ^ aStream
+	].
     ].
 
     "/
@@ -2233,39 +2237,39 @@
     "/
     who := self who.
     who notNil ifTrue:[
-        myClass := who methodClass.
-
-        (package notNil and:[package ~= myClass package and:[package ~= #'__NoProject__']]) ifTrue:[
-            "/ I am an extension
-            mgr notNil ifTrue:[
-                "/ try to get the source using my package information ...
-                mod := package asPackageId module.
-                dir := package asPackageId directory.
-                aStream := mgr streamForExtensionFile:source package:package directory:dir module:mod cache:true.
-                aStream notNil ifTrue:[
-                    usingCacheBoolean ifTrue:[
-                        self cacheSourceStream:aStream.
-                    ].
-                    ^ aStream
-                ].
-            ].
-            "/ consult the local fileSystem
-            aStream := self localSourceStream.
-            aStream notNil ifTrue:[
-                usingCacheBoolean ifTrue:[
-                    self cacheSourceStream:aStream.
-                ].
-                ^ aStream
-            ]
-        ].
-
-        aStream := myClass sourceStreamFor:source.
-        aStream notNil ifTrue:[
-            usingCacheBoolean ifTrue:[
-                self cacheSourceStream:aStream.
-            ].
-            ^ aStream
-        ].
+	myClass := who methodClass.
+
+	(package notNil and:[package ~= myClass package and:[package ~= #'__NoProject__']]) ifTrue:[
+	    "/ I am an extension
+	    mgr notNil ifTrue:[
+		"/ try to get the source using my package information ...
+		mod := package asPackageId module.
+		dir := package asPackageId directory.
+		aStream := mgr streamForExtensionFile:source package:package directory:dir module:mod cache:true.
+		aStream notNil ifTrue:[
+		    usingCacheBoolean ifTrue:[
+			self cacheSourceStream:aStream.
+		    ].
+		    ^ aStream
+		].
+	    ].
+	    "/ consult the local fileSystem
+	    aStream := self localSourceStream.
+	    aStream notNil ifTrue:[
+		usingCacheBoolean ifTrue:[
+		    self cacheSourceStream:aStream.
+		].
+		^ aStream
+	    ]
+	].
+
+	aStream := myClass sourceStreamFor:source.
+	aStream notNil ifTrue:[
+	    usingCacheBoolean ifTrue:[
+		self cacheSourceStream:aStream.
+	    ].
+	    ^ aStream
+	].
     ].
 
     "/
@@ -2273,49 +2277,49 @@
     "/ (if there is a source-code manager - otherwise, we already did that)
     "/
     (mgr notNil and:[Class tryLocalSourceFirst not]) ifTrue:[
-        aStream := self localSourceStream.
-        aStream notNil ifTrue:[
-            usingCacheBoolean ifTrue:[
-                self cacheSourceStream:aStream.
-            ].
-            ^ aStream
-        ].
+	aStream := self localSourceStream.
+	aStream notNil ifTrue:[
+	    usingCacheBoolean ifTrue:[
+		self cacheSourceStream:aStream.
+	    ].
+	    ^ aStream
+	].
     ].
 
     "/
     "/ final chance: try current directory
     "/
     aStream isNil ifTrue:[
-        aStream := source asFilename readStreamOrNil.
-        aStream notNil ifTrue:[
-            usingCacheBoolean ifTrue:[
-                self cacheSourceStream:aStream.
-            ].
-            ^ aStream
-        ].
+	aStream := source asFilename readStreamOrNil.
+	aStream notNil ifTrue:[
+	    usingCacheBoolean ifTrue:[
+		self cacheSourceStream:aStream.
+	    ].
+	    ^ aStream
+	].
     ].
 
     (who isNil and:[source notNil]) ifTrue:[
-        "/
-        "/ mhmh - seems to be a method which used to be in some
-        "/ class, but has been overwritten by another or removed.
-        "/ (i.e. it has no containing class anyMore)
-        "/ try to guess the class from the sourceFileName.
-        "/ and retry.
-        "/
-        className := Smalltalk classNameForFile:source.
-        (classNameSymbol := className asSymbolIfInterned) notNil ifTrue:[
-            myClass := Smalltalk at:classNameSymbol ifAbsent:nil.
-            myClass notNil ifTrue:[
-                aStream := myClass sourceStreamFor:source.
-                aStream notNil ifTrue:[
-                    usingCacheBoolean ifTrue:[
-                        self cacheSourceStream:aStream.
-                    ].
-                    ^ aStream
-                ].
-            ]
-        ]
+	"/
+	"/ mhmh - seems to be a method which used to be in some
+	"/ class, but has been overwritten by another or removed.
+	"/ (i.e. it has no containing class anyMore)
+	"/ try to guess the class from the sourceFileName.
+	"/ and retry.
+	"/
+	className := Smalltalk classNameForFile:source.
+	(classNameSymbol := className asSymbolIfInterned) notNil ifTrue:[
+	    myClass := Smalltalk at:classNameSymbol ifAbsent:nil.
+	    myClass notNil ifTrue:[
+		aStream := myClass sourceStreamFor:source.
+		aStream notNil ifTrue:[
+		    usingCacheBoolean ifTrue:[
+			self cacheSourceStream:aStream.
+		    ].
+		    ^ aStream
+		].
+	    ]
+	]
     ].
 
     ^ nil
@@ -2327,8 +2331,8 @@
     "set the lookupObject (low level - use lookupObject:)"
 
     lookupObject ~~ lookup ifTrue:[
-        lookupObject := lookup.
-        ObjectMemory flushCaches.
+	lookupObject := lookup.
+	ObjectMemory flushCaches.
     ].
 
     "Created: / 11-07-2010 / 19:31:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -2336,9 +2340,9 @@
 
 sourceChunkFromStream:aStream
     PositionError handle:[:ex |
-        ^ nil
+	^ nil
     ] do:[
-        aStream position:(sourcePosition ? 1) abs - 1.
+	aStream position:(sourcePosition ? 1) abs - 1.
     ].
     ^ aStream nextChunk.
 !
@@ -2353,7 +2357,7 @@
 
     rawStream := self rawSourceStreamUsingCache:usingCacheBoolean.
     rawStream isNil ifTrue:[
-        ^ nil.
+	^ nil.
     ].
     rawStream position:0.
 
@@ -2374,7 +2378,7 @@
     OBJ nr = 0;
 
     if (f & F_PRIMITIVE) {
-        nr = __INST(code_);
+	nr = __INST(code_);
     }
     RETURN (nr);
 #endif
@@ -2428,15 +2432,15 @@
 
     src := self source.
     src notNil ifTrue:[
-        parser := Parser
-                        parseMethod:src
-                        in:self containingClass
-                        ignoreErrors:true
-                        ignoreWarnings:true.
-
-        (parser notNil and:[parser ~~ #Error]) ifTrue:[
-            ^ parser usedInstVars
-        ].
+	parser := Parser
+			parseMethod:src
+			in:self containingClass
+			ignoreErrors:true
+			ignoreWarnings:true.
+
+	(parser notNil and:[parser ~~ #Error]) ifTrue:[
+	    ^ parser usedInstVars
+	].
     ].
     ^ #() "/ actually: unknown
 
@@ -2471,7 +2475,7 @@
 containingClass
     "return the class I am defined in.
      Notice, that the containingClass query returns nil, if a method is wrapped or no longer valid
-     due to an accept in a browser or debugger. 
+     due to an accept in a browser or debugger.
      However, the mclass slot still contains a reference to the once valid class and can be fetched
      via getMclass.
      See comment in who."
@@ -2481,17 +2485,17 @@
     |who|
 
     mclass notNil ifTrue:[
-        "/ check if this (cached) info is still valid...
-        (mclass containsMethod:self) ifTrue:[
-            ^ mclass
-        ].
-        ^ nil.
+	"/ check if this (cached) info is still valid...
+	(mclass containsMethod:self) ifTrue:[
+	    ^ mclass
+	].
+	^ nil.
     ].
 
     who := self who.
     who notNil ifTrue:[
-        mclass := who methodClass.
-        ^ mclass
+	mclass := who methodClass.
+	^ mclass
     ].
     "
      none found - sorry
@@ -2512,38 +2516,38 @@
     |newMethod function|
 
     (self
-        literalsDetect:[:lit |
-            #(
-                #'invoke'
-                #'invokeWith:'
-                #'invokeWith:with:'
-                #'invokeWith:with:with:'
-                #'invokeWith:with:with:with:'
-                #'invokeWithArguments:'
-                #'invokeCPPVirtualOn:'
-                #'invokeCPPVirtualOn:with:'
-                #'invokeCPPVirtualOn:with:with:'
-                #'invokeCPPVirtualOn:with:with:with:'
-                #'invokeCPPVirtualOn:with:with:with:with:'
-                #'invokeCPPVirtualOn:withArguments:'
-            ) includes:lit
-        ]
-        ifNone:nil) notNil
+	literalsDetect:[:lit |
+	    #(
+		#'invoke'
+		#'invokeWith:'
+		#'invokeWith:with:'
+		#'invokeWith:with:with:'
+		#'invokeWith:with:with:with:'
+		#'invokeWithArguments:'
+		#'invokeCPPVirtualOn:'
+		#'invokeCPPVirtualOn:with:'
+		#'invokeCPPVirtualOn:with:with:'
+		#'invokeCPPVirtualOn:with:with:with:'
+		#'invokeCPPVirtualOn:with:with:with:with:'
+		#'invokeCPPVirtualOn:withArguments:'
+	    ) includes:lit
+	]
+	ifNone:nil) notNil
     ifTrue:[
-        "/ sigh - for stc-compiled code, this does not work:
-        function := self literalsDetect:[:lit | lit isExternalLibraryFunction] ifNone:nil.
-        function isNil ifTrue:[
-            "/ parse it and ask the parser
-            newMethod := Compiler compile:self source forClass:self mclass install:false.
-            function := newMethod literalsDetect:[:lit | lit isExternalLibraryFunction] ifNone:nil.
-        ].
-        ^ function
+	"/ sigh - for stc-compiled code, this does not work:
+	function := self literalsDetect:[:lit | lit isExternalLibraryFunction] ifNone:nil.
+	function isNil ifTrue:[
+	    "/ parse it and ask the parser
+	    newMethod := Compiler compile:self source forClass:self mclass install:false.
+	    function := newMethod literalsDetect:[:lit | lit isExternalLibraryFunction] ifNone:nil.
+	].
+	^ function
     ].
     ^ nil
 
     "
      (IDispatchPointer compiledMethodAt:#'invokeGetTypeInfo:_:_:')
-        externalLibraryFunction
+	externalLibraryFunction
     "
 !
 
@@ -2573,7 +2577,7 @@
 
     "
      Method allInstancesDo:[:m |
-        (m hasAnyResource:#(image canvas)) ifTrue:[self halt]
+	(m hasAnyResource:#(image canvas)) ifTrue:[self halt]
      ].
     "
 !
@@ -2589,10 +2593,10 @@
 
     src := self source.
     src notNil ifTrue:[
-        (src includesString:(String with:$% with:${) "<- no constant here - to avoid trouble with stupid scanners" ) ifFalse:[
-            "/ cannot contain primitive code.
-            ^ false
-        ]
+	(src includesString:(String with:$% with:${) "<- no constant here - to avoid trouble with stupid scanners" ) ifFalse:[
+	    "/ cannot contain primitive code.
+	    ^ false
+	]
     ].
 
     "/ ok; it may or may not ...
@@ -2687,20 +2691,20 @@
 
     m := self trapMethodForNumArgs:(self argumentCount).
     (m notNil and:[self ~~ m]) ifTrue:[
-        (myCode notNil and:[myCode = m code]) ifTrue:[^ true].
-        (byteCode notNil and:[byteCode == m byteCode]) ifTrue:[^ true].
+	(myCode notNil and:[myCode = m code]) ifTrue:[^ true].
+	(byteCode notNil and:[byteCode == m byteCode]) ifTrue:[^ true].
     ].
 
     m := Method compiledMethodAt:#uncompiledCodeObject.
     (m notNil and:[self ~~ m]) ifTrue:[
-        (myCode notNil and:[myCode = m code]) ifTrue:[^ true].
-        (byteCode notNil and:[byteCode == m byteCode]) ifTrue:[^ true].
+	(myCode notNil and:[myCode = m code]) ifTrue:[^ true].
+	(byteCode notNil and:[byteCode == m byteCode]) ifTrue:[^ true].
     ].
 
     m := Method compiledMethodAt:#unloadedCodeObject.
     (m notNil and:[self ~~ m]) ifTrue:[
-        (myCode notNil and:[myCode = m code]) ifTrue:[^ true].
-        (byteCode notNil and:[byteCode == m byteCode]) ifTrue:[^ true].
+	(myCode notNil and:[myCode = m code]) ifTrue:[^ true].
+	(byteCode notNil and:[byteCode == m byteCode]) ifTrue:[^ true].
     ].
 
     ^ false
@@ -2781,7 +2785,7 @@
 mclass
     "return the class in which the receiver is currently contained in.
      Notice, that the mclass query returns nil, if a method is wrapped or no longer valid
-     due to an accept in a browser or debugger. 
+     due to an accept in a browser or debugger.
      However, the mclass slot still contains a reference to the once valid class and can be fetched
      via getMclass.
      Same as #containingClass, for ST80 compatibility."
@@ -2815,11 +2819,11 @@
      (Method compiledMethodAt:#printOn:) messagesSent
      (Point compiledMethodAt:#x:) messagesSent
 
-     (WindowEvent class compiledMethodAt:#focusInView:) messagesSent  
-     (WindowEvent class compiledMethodAt:#focusInView:) messagesPossiblySent  
-
-     (Method compiledMethodAt:#messagesPossiblySent) messagesSent  
-     (Method compiledMethodAt:#messagesPossiblySent) messagesPossiblySent 
+     (WindowEvent class compiledMethodAt:#focusInView:) messagesSent
+     (WindowEvent class compiledMethodAt:#focusInView:) messagesPossiblySent
+
+     (Method compiledMethodAt:#messagesPossiblySent) messagesSent
+     (Method compiledMethodAt:#messagesPossiblySent) messagesPossiblySent
     "
 !
 
@@ -2856,7 +2860,7 @@
     "return a collection with the methods argument and variable names.
      Uses Parser to parse methods source and extract the names.
      Returns an empty collection if the source is not available, or some other
-     syntax/parse error occurred. 
+     syntax/parse error occurred.
      For methods with no args and no vars, an empty collection is returned."
 
     |parserClass parser sourceString argNames varNames|
@@ -2864,13 +2868,13 @@
     parserClass := self parserClass.
     sourceString := self source.
     (parserClass notNil and:[sourceString notNil]) ifTrue:[
-        parser := parserClass parseMethodArgAndVarSpecificationSilent:sourceString.
-        (parser isNil or:[parser == #Error]) ifTrue:[^ #()].
-        argNames := parser methodArgs.
-        varNames := parser methodVars.
-        argNames isNil ifTrue:[^ varNames ? #()].
-        varNames isNil ifTrue:[^ argNames ? #()].
-        ^ (argNames , varNames)
+	parser := parserClass parseMethodArgAndVarSpecificationSilent:sourceString.
+	(parser isNil or:[parser == #Error]) ifTrue:[^ #()].
+	argNames := parser methodArgs.
+	varNames := parser methodVars.
+	argNames isNil ifTrue:[^ varNames ? #()].
+	varNames isNil ifTrue:[^ argNames ? #()].
+	^ (argNames , varNames)
     ].
     ^ #()
 
@@ -2885,9 +2889,9 @@
      Returns nil if the source is not available, or some other
      syntax/parse error occurred. For methods with no args and no vars,
      an empty collection is returned."
-    
+
      ^self methodArgAndVarNames
-    
+
      "Created: / 18-12-2012 / 18:17:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
@@ -2916,30 +2920,30 @@
     line := (text at:2).
     nQuote := line occurrencesOf:(Character doubleQuote).
     (nQuote == 2) ifTrue:[
-        qIndex := line indexOf:(Character doubleQuote).
-        qIndex2 := line indexOf:(Character doubleQuote) startingAt:(qIndex + 1).
-        ^ line copyFrom:(qIndex + 1) to:(qIndex2 - 1)
+	qIndex := line indexOf:(Character doubleQuote).
+	qIndex2 := line indexOf:(Character doubleQuote) startingAt:(qIndex + 1).
+	^ line copyFrom:(qIndex + 1) to:(qIndex2 - 1)
     ].
     (nQuote == 1) ifTrue:[
-        qIndex := line indexOf:(Character doubleQuote).
-        comment := line copyFrom:(qIndex + 1).
-        (line indexOf:$/ startingAt:qIndex) == (qIndex+1) ifTrue:[
-            "/ an EOL comment
-            ^ (comment copyFrom:2) withoutSeparators
-        ].
-
-        "/ not an EOL comment
-        index := 3.
-        line := text at:index.
-        nQuote := line occurrencesOf:(Character doubleQuote).
-        [nQuote ~~ 1] whileTrue:[
-            comment := comment , Character cr asString , line withoutSpaces.
-            index := index + 1.
-            line := text at:index.
-            nQuote := line occurrencesOf:(Character doubleQuote)
-        ].
-        qIndex := line indexOf:(Character doubleQuote).
-        ^ comment , Character cr asString , (line copyTo:(qIndex - 1)) withoutSpaces
+	qIndex := line indexOf:(Character doubleQuote).
+	comment := line copyFrom:(qIndex + 1).
+	(line indexOf:$/ startingAt:qIndex) == (qIndex+1) ifTrue:[
+	    "/ an EOL comment
+	    ^ (comment copyFrom:2) withoutSeparators
+	].
+
+	"/ not an EOL comment
+	index := 3.
+	line := text at:index.
+	nQuote := line occurrencesOf:(Character doubleQuote).
+	[nQuote ~~ 1] whileTrue:[
+	    comment := comment , Character cr asString , line withoutSpaces.
+	    index := index + 1.
+	    line := text at:index.
+	    nQuote := line occurrencesOf:(Character doubleQuote)
+	].
+	qIndex := line indexOf:(Character doubleQuote).
+	^ comment , Character cr asString , (line copyTo:(qIndex - 1)) withoutSpaces
     ].
     ^ nil
 
@@ -2952,8 +2956,8 @@
     "return the string that defines the method and the arguments"
 
     ^ self class
-        methodDefinitionTemplateForSelector:self selector
-        andArgumentNames:self methodArgNames
+	methodDefinitionTemplateForSelector:self selector
+	andArgumentNames:self methodArgNames
 
     "
       (self compiledMethodAt:#printOn:) methodDefinitionTemplate
@@ -2996,8 +3000,8 @@
     list isEmptyOrNil ifTrue:[^ nil].
     histLine := list last.
     ^ Timestamp
-        fromDate:histLine date
-        andTime:histLine time
+	fromDate:histLine date
+	andTime:histLine time
 
     "
      (Method compiledMethodAt:#modificationTime) modificationTime
@@ -3038,8 +3042,8 @@
     | mth |
     mth := self overwrittenMethod.
     [ mth notNil ] whileTrue:
-        [mth == aMethod ifTrue:[^true].
-        mth := mth overwrittenMethod].
+	[mth == aMethod ifTrue:[^true].
+	mth := mth overwrittenMethod].
     ^false
 
     "Created: / 05-07-2012 / 10:52:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -3054,7 +3058,7 @@
 
     "
      (Method compiledMethodAt:#parse:return:or:)
-        parse:#'parseMethodSilent:' return:#sentMessages or:#()
+	parse:#'parseMethodSilent:' return:#sentMessages or:#()
     "
 !
 
@@ -3071,35 +3075,35 @@
     "/ is very common with the new browser's info displays, we cache a few
     "/ of them. If the same is parsed soon after, we do not have to parse again.
     LastParseTreeCache notNil ifTrue:[
-        "/ to flush: LastParseTreeCache removeAll.
-        cachedInfo := LastParseTreeCache at:self ifAbsent:nil.
-        cachedInfo notNil ifTrue:[
-            cachedInfo method == self ifTrue:[
-                cachedInfo parserClass == parserClass ifTrue:[
-                    "/ Transcript show:'hit '; showCR:self.
-                    ^ cachedInfo parser perform:accessSelector
-                ]
-            ].
-            LastParseTreeCache removeKey:self
-        ]
+	"/ to flush: LastParseTreeCache removeAll.
+	cachedInfo := LastParseTreeCache at:self ifAbsent:nil.
+	cachedInfo notNil ifTrue:[
+	    cachedInfo method == self ifTrue:[
+		cachedInfo parserClass == parserClass ifTrue:[
+		    "/ Transcript show:'hit '; showCR:self.
+		    ^ cachedInfo parser perform:accessSelector
+		]
+	    ].
+	    LastParseTreeCache removeKey:self
+	]
     ].
 
     sourceString := self source.
     (parserClass notNil and:[sourceString notNil]) ifTrue:[
-        parseSelector argumentCount == 2 ifTrue:[
-            parser := parserClass perform:parseSelector with:sourceString with:arg2.
-        ] ifFalse:[
-            parser := parserClass perform:parseSelector with:sourceString.
-        ].
-        (parser isNil or:[parser == #Error]) ifTrue:[^ valueIfNoSource].
-        "do not cache the parser, if it was parsing for code - a lot of information is missing then"
-        (self mclass notNil and:[parser wasParsedForCode not]) ifTrue:[
-            LastParseTreeCache isNil ifTrue:[
-                LastParseTreeCache := CacheDictionary new:500.
-            ].
-            LastParseTreeCache at:self put:(ParserCacheEntry new parserClass:parserClass method:self parser:parser).
-        ].
-        ^ parser perform:accessSelector
+	parseSelector argumentCount == 2 ifTrue:[
+	    parser := parserClass perform:parseSelector with:sourceString with:arg2.
+	] ifFalse:[
+	    parser := parserClass perform:parseSelector with:sourceString.
+	].
+	(parser isNil or:[parser == #Error]) ifTrue:[^ valueIfNoSource].
+	"do not cache the parser, if it was parsing for code - a lot of information is missing then"
+	(self mclass notNil and:[parser wasParsedForCode not]) ifTrue:[
+	    LastParseTreeCache isNil ifTrue:[
+		LastParseTreeCache := CacheDictionary new:500.
+	    ].
+	    LastParseTreeCache at:self put:(ParserCacheEntry new parserClass:parserClass method:self parser:parser).
+	].
+	^ parser perform:accessSelector
     ].
     ^ valueIfNoSource
 
@@ -3107,7 +3111,7 @@
      LastParseTreeCache removeAll.
 
      (Method compiledMethodAt:#parse:return:or:)
-        parse:#'parseMethodSilent:' return:#sentMessages or:#()
+	parse:#'parseMethodSilent:' return:#sentMessages or:#()
     "
 
     "Modified: / 01-03-2012 / 14:30:50 / cg"
@@ -3121,15 +3125,15 @@
 
     src := self source.
     src isNil ifTrue:[
-        ^ nil "/ actually: dont know
+	^ nil "/ actually: dont know
     ].
 
     self parserClass isNil ifTrue:[
-        ^ nil
+	^ nil
     ].
     parser := self parserClass parseMethod: src.
     (parser isNil or: [parser == #Error]) ifTrue:[
-        ^ nil "/ actually error
+	^ nil "/ actually error
     ].
     ^ annotations := parser annotations.
 
@@ -3139,26 +3143,26 @@
 parseResources
     "return the method's resource spec; either nil or a collection of symbols.
      Resources are a special kind of annotation, of the form:
-        <resource: #symbol...>
+	<resource: #symbol...>
      and flags methods which depend on keyboard bindings or provide menus, specs or bitmap images"
 
     |src parser|
 
     src := self source.
     src isNil ifTrue:[
-        ^ nil "/ actually: dont know
+	^ nil "/ actually: dont know
     ].
 
     (src findString:'resource:') == 0 ifTrue:[
-        ^ nil "/ actually: error
+	^ nil "/ actually: error
     ].
     "/ no need to parse all - only interested in resource-info
     self parserClass isNil ifTrue:[
-        ^ nil
+	^ nil
     ].
     parser := self parserClass parseMethodArgAndVarSpecificationSilent:src in:nil.
     parser isNil ifTrue:[
-        ^ nil "/ actually error
+	^ nil "/ actually error
     ].
     ^ parser primitiveResources.
 !
@@ -3168,7 +3172,7 @@
      (such as perform) with aSelectorSymbol as selector."
 
     (self referencesLiteral:aSelectorSymbol) ifTrue:[
-        ^ self messagesPossiblySent includesIdentical:aSelectorSymbol
+	^ self messagesPossiblySent includesIdentical:aSelectorSymbol
     ].
     ^ false
 !
@@ -3258,31 +3262,31 @@
     versions := OrderedCollection new.
 
     ChangeSet current reverseDo:[:change |
-        (change isMethodChange
-            and:[ (change selector == sel)
-            and:[ change changeClass == cls ]])
-        ifTrue:[
-            versions addFirst:change.
-            lastChange := change.
-            (count notNil and:[versions size == count]) ifTrue:[
-                ^ versions
-            ]
-        ]
+	(change isMethodChange
+	    and:[ (change selector == sel)
+	    and:[ change changeClass == cls ]])
+	ifTrue:[
+	    versions addFirst:change.
+	    lastChange := change.
+	    (count notNil and:[versions size == count]) ifTrue:[
+		^ versions
+	    ]
+	]
     ].
 
     lastChange notNil ifTrue:[
-        last := lastChange previousVersion.
-        last notNil ifTrue:[
-            firstSrc := last source.
-            (firstSrc notEmptyOrNil
-            and:[ firstSrc ~= lastChange source]) ifTrue:[
-                versions addFirst:(MethodDefinitionChange
-                                    className:lastChange className
-                                    selector:lastChange selector
-                                    source:firstSrc
-                                    category:lastChange category).
-            ]
-        ]
+	last := lastChange previousVersion.
+	last notNil ifTrue:[
+	    firstSrc := last source.
+	    (firstSrc notEmptyOrNil
+	    and:[ firstSrc ~= lastChange source]) ifTrue:[
+		versions addFirst:(MethodDefinitionChange
+				    className:lastChange className
+				    selector:lastChange selector
+				    source:firstSrc
+				    category:lastChange category).
+	    ]
+	]
     ].
     ^ versions
 
@@ -3324,10 +3328,10 @@
     (super refersToLiteral: anObject) ifTrue:[^ true].
 
     self annotationsDo:[:annot |
-        (annot refersToLiteral: anObject) ifTrue:[
-            "/ self halt.
-            ^ true
-        ].
+	(annot refersToLiteral: anObject) ifTrue:[
+	    "/ self halt.
+	    ^ true
+	].
     ].
     ^ false
 
@@ -3338,10 +3342,10 @@
     (super refersToLiteralMatching: aMatchString) ifTrue:[^ true].
 
     self annotationsDo:[:annot |
-        (annot refersToLiteralMatching: aMatchString) ifTrue:[
-            "/ self halt.
-            ^ true
-        ].
+	(annot refersToLiteralMatching: aMatchString) ifTrue:[
+	    "/ self halt.
+	    ^ true
+	].
     ].
     ^ false
 
@@ -3356,9 +3360,9 @@
     |resources|
 
     (resources := self resources) notNil ifTrue:[
-        resources keysAndValuesDo:[:key :val|
-            ^ key
-        ].
+	resources keysAndValuesDo:[:key :val|
+	    ^ key
+	].
     ].
     ^ nil
 !
@@ -3373,7 +3377,7 @@
 
     resources := IdentityDictionary new.
     self annotationsAt: #resource: orAt: #resource:value: do:[:annot|
-        resources at: annot type put: annot value ? true
+	resources at: annot type put: annot value ? true
     ].
     ^ resources
 
@@ -3411,12 +3415,12 @@
      with aSelectorSymbol as selector."
 
     (self referencesLiteral:aSelectorSymbol) ifTrue:[
-        "/ cg: was temporarily disabled to speed up some searches.
-        "/ I think, we have to change the caller's to call referencesLiteral: instead,
-        "/ if there is any speed problem there. Not here.
-        "/ ^ true.
-
-        ^ self messagesSent includesIdentical:aSelectorSymbol
+	"/ cg: was temporarily disabled to speed up some searches.
+	"/ I think, we have to change the caller's to call referencesLiteral: instead,
+	"/ if there is any speed problem there. Not here.
+	"/ ^ true.
+
+	^ self messagesSent includesIdentical:aSelectorSymbol
     ].
     ^ false
 !
@@ -3438,13 +3442,13 @@
     |msgs|
 
     (aCollectionOfSelectorSymbols contains:[:sym | self referencesLiteral:sym]) ifTrue:[
-        "/ cg: was temporarily disabled to speed up some searches.
-        "/ I think, we have to change the caller's to call referencesLiteral: instead,
-        "/ if there is any speed problem there. Not here.
-        "/ ^ true.
-
-        msgs := self messagesSent.
-        ^ aCollectionOfSelectorSymbols contains:[:sym | msgs includesIdentical:sym]
+	"/ cg: was temporarily disabled to speed up some searches.
+	"/ I think, we have to change the caller's to call referencesLiteral: instead,
+	"/ if there is any speed problem there. Not here.
+	"/ ^ true.
+
+	msgs := self messagesSent.
+	^ aCollectionOfSelectorSymbols contains:[:sym | msgs includesIdentical:sym]
     ].
     ^ false
 
@@ -3463,16 +3467,16 @@
     nonMetaClass := myClass theNonMetaclass.
 
     (package ~= nonMetaClass package
-        and:[ package ~= PackageId noProjectID
-        and:[ (myProjectDefinition := nonMetaClass projectDefinitionClass) notNil ]])
-    ifTrue:[ 
-        originalMethod := myProjectDefinition savedOverwrittenMethodForClass:myClass selector:self selector.
-
-        "/ mhm - what if it does no make a difference?
-        "/ (originalMethod notNil and:[originalMethod source = self source]) ifTrue:[
-        "/    "/ self halt. ^ nil
-        "/ ].
-        ^ originalMethod
+	and:[ package ~= PackageId noProjectID
+	and:[ (myProjectDefinition := nonMetaClass projectDefinitionClass) notNil ]])
+    ifTrue:[
+	originalMethod := myProjectDefinition savedOverwrittenMethodForClass:myClass selector:self selector.
+
+	"/ mhm - what if it does no make a difference?
+	"/ (originalMethod notNil and:[originalMethod source = self source]) ifTrue:[
+	"/    "/ self halt. ^ nil
+	"/ ].
+	^ originalMethod
     ].
     ^ nil
 
@@ -3525,41 +3529,41 @@
      nil is returned for unbound methods.
 
      ST/X special notice:
-        returns an instance of MethodWhoInfo, which
-        responds to #methodClass and #methodSelector query messages.
-        For backward- (& ST-80) compatibility, the returned object also
-        responds to #at:1 and #at:2 messages.
+	returns an instance of MethodWhoInfo, which
+	responds to #methodClass and #methodSelector query messages.
+	For backward- (& ST-80) compatibility, the returned object also
+	responds to #at:1 and #at:2 messages.
 
      Implementation notice:
-        To avoid an expensive search, the once valid containing class is kept and remembered
-        in the mclass slot. However, if a method gets recompiled or wrapped, the mclass field is
-        no longer valid and who on the old method returns nil (because the method is actually no longer
-        contained in that class). However, to allow easier unwrapping (and gathering of the corresponding
-        wrapper), the mclass field is never nilled. I.e. it still refers to the original class.
-        Therefore, a validation of the mclass slot is done here."
+	To avoid an expensive search, the once valid containing class is kept and remembered
+	in the mclass slot. However, if a method gets recompiled or wrapped, the mclass field is
+	no longer valid and who on the old method returns nil (because the method is actually no longer
+	contained in that class). However, to allow easier unwrapping (and gathering of the corresponding
+	wrapper), the mclass field is never nilled. I.e. it still refers to the original class.
+	Therefore, a validation of the mclass slot is done here."
 
     |cls sel fn clsName checkBlock|
 
     mclass notNil ifTrue:[
-        "/ check if this (cached) info is still valid...
-        sel := mclass selectorAtMethod:self.
-        sel notNil ifTrue:[
-            ^ MethodWhoInfo class:mclass selector:sel
-        ].
-        ^ nil.
+	"/ check if this (cached) info is still valid...
+	sel := mclass selectorAtMethod:self.
+	sel notNil ifTrue:[
+	    ^ MethodWhoInfo class:mclass selector:sel
+	].
+	^ nil.
     ].
 
-    checkBlock := 
-        [:cls |
-            |sel|
-
-            sel := cls selectorAtMethod:self.
-            sel notNil ifTrue:[
-                LastWhoClass := cls theNonMetaclass name.
-                mclass := cls.
-                ^ MethodWhoInfo class:cls selector:sel
-            ].
-        ].
+    checkBlock :=
+	[:cls |
+	    |sel|
+
+	    sel := cls selectorAtMethod:self.
+	    sel notNil ifTrue:[
+		LastWhoClass := cls theNonMetaclass name.
+		mclass := cls.
+		^ MethodWhoInfo class:cls selector:sel
+	    ].
+	].
 
     "
      first, look in the class we found something the last time
@@ -3568,11 +3572,11 @@
      being garbage collected)
     "
     LastWhoClass notNil ifTrue:[
-        cls := Smalltalk at:LastWhoClass ifAbsent:nil.
-        cls notNil ifTrue:[
-            checkBlock value:cls theNonMetaclass.
-            checkBlock value:cls theMetaclass.
-        ]
+	cls := Smalltalk at:LastWhoClass ifAbsent:nil.
+	cls notNil ifTrue:[
+	    checkBlock value:cls theNonMetaclass.
+	    checkBlock value:cls theMetaclass.
+	]
     ].
 
     "
@@ -3580,15 +3584,15 @@
      extract the className from it and try that class first.
     "
     (fn := self sourceFilename) notNil ifTrue:[
-        clsName := fn asFilename nameWithoutSuffix.
-        clsName := clsName asSymbolIfInterned.
-        clsName notNil ifTrue:[
-            cls := Smalltalk at:clsName ifAbsent:nil.
-            cls notNil ifTrue:[
-                checkBlock value:cls theNonMetaclass.
-                checkBlock value:cls theMetaclass.
-            ]
-        ].
+	clsName := fn asFilename nameWithoutSuffix.
+	clsName := clsName asSymbolIfInterned.
+	clsName notNil ifTrue:[
+	    cls := Smalltalk at:clsName ifAbsent:nil.
+	    cls notNil ifTrue:[
+		checkBlock value:cls theNonMetaclass.
+		checkBlock value:cls theMetaclass.
+	    ]
+	].
     ].
 
     "
@@ -3596,8 +3600,8 @@
      since probability is high, that the receiver is found in there ...
     "
     Smalltalk allClassesDo:[:cls |
-        checkBlock value:cls theNonMetaclass.
-        checkBlock value:cls theMetaclass.
+	checkBlock value:cls theNonMetaclass.
+	checkBlock value:cls theMetaclass.
     ].
 
     LastWhoClass := nil.
@@ -3627,11 +3631,11 @@
      |m cls|
 
      Object
-        subclass:#FunnyClass
-        instanceVariableNames:'foo'
-        classVariableNames:''
-        poolDictionaries:''
-        category:'testing'.
+	subclass:#FunnyClass
+	instanceVariableNames:'foo'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'testing'.
      cls := Smalltalk at:#FunnyClass.
      Smalltalk removeClass:cls.
 
@@ -3650,9 +3654,9 @@
      That's the WrapperMethod which contains myself."
 
     WrappedMethod notNil ifTrue:[
-        WrappedMethod allInstancesDo:[:m |
-            m originalMethod == self ifTrue:[^ m].
-        ].
+	WrappedMethod allInstancesDo:[:m |
+	    m originalMethod == self ifTrue:[^ m].
+	].
     ].
     ^ nil
 
@@ -3760,17 +3764,17 @@
     This was done, since a smalltalk method cannot return multiple
     values, but 2 values had to be returned from that method.
     Thus, the who-interface was used as:
-        info := <someMethod> who.
-        class := info at:1.
-        sel := info at:2.
+	info := <someMethod> who.
+	class := info at:1.
+	sel := info at:2.
 
     Sure, this is ugly coding style, and the system has been changed to return
     an object (an instance of MethodWhoInfo) which responds to the two
     messages: #methodClass and #methodSelector.
     This allows to write things much more intuitive:
-        info := <someMethod> who.
-        class := info methodClass.
-        sel := info methodSelector.
+	info := <someMethod> who.
+	class := info methodClass.
+	sel := info methodSelector.
 
     However, to be backward compatible, the returned object still responds to
     the #at: message, but only allows inices of 1 and 2 to be used.
@@ -3779,10 +3783,10 @@
     classes.
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [see also:]
-        Method
+	Method
 "
 ! !
 
@@ -3831,10 +3835,10 @@
     "simulate the old behavior (when Method>>who returned an array)"
 
     index == 1 ifTrue:[
-        ^ myClass
+	^ myClass
     ].
     index == 2 ifTrue:[
-        ^ mySelector
+	^ mySelector
     ].
 
     "/ sigh - full compatibility ?
@@ -3931,11 +3935,11 @@
 !Method class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.465 2015-06-08 15:50:12 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.465 2015-06-08 15:50:12 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/Object.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/Object.st	Fri Jul 24 08:06:37 2015 +0100
@@ -3459,7 +3459,7 @@
 	    deps class == WeakArray ifTrue:[
 		dep := deps at:1.
 		dep ~~ anObject ifTrue:[
-		    (dep isNil or:[dep == 0]) ifTrue:[
+		    (dep isNil or:[dep class == SmallInteger]) ifTrue:[
 			deps at:1 put:anObject
 		    ] ifFalse:[
 			self dependents:(WeakIdentitySet with:dep with:anObject)
@@ -3562,7 +3562,7 @@
     deps := self dependents.
     deps size ~~ 0 ifTrue:[
 	deps do:[:d |
-		    (d notNil and:[d ~~ 0]) ifTrue:[
+		    (d notNil and:[d class ~~ SmallInteger]) ifTrue:[
 			aBlock value:d
 		    ]
 		]
@@ -3615,7 +3615,7 @@
 	    ((deps class == WeakArray) or:[deps class == Array]) ifTrue:[
 		((d := deps at:1) == anObject
 		or:[d isNil
-		or:[d == 0]]) ifTrue:[
+		or:[d class == SmallInteger]]) ifTrue:[
 		    self dependents:nil
 		]
 	    ] ifFalse:[
@@ -5272,6 +5272,7 @@
 "/        ] do:[
 "/           Processor activeProcess terminate.
 "/        ].
+	MiniDebugger enter.
 	Processor activeProcess terminateNoSignal.
     ].
 
@@ -6566,7 +6567,7 @@
      If the message expects an argument, pass arg."
 
     aSelector argumentCount == 1 ifTrue:[
-        ^ self perform:aSelector with:arg
+	^ self perform:aSelector with:arg
     ].
     ^ self perform:aSelector
 
@@ -6591,10 +6592,10 @@
 
     numArgs := aSelector argumentCount.
     numArgs == 0 ifTrue:[
-        ^ self perform:aSelector
+	^ self perform:aSelector
     ].
     numArgs == 1 ifTrue:[
-        ^ self perform:aSelector with:optionalArg1
+	^ self perform:aSelector with:optionalArg1
     ].
     ^ self perform:aSelector with:optionalArg1 with:optionalArg2.
 
@@ -6619,13 +6620,13 @@
 
     numArgs := aSelector argumentCount.
     numArgs == 0 ifTrue:[
-        ^ self perform:aSelector
+	^ self perform:aSelector
     ].
     numArgs == 1 ifTrue:[
-        ^ self perform:aSelector with:optionalArg1
+	^ self perform:aSelector with:optionalArg1
     ].
     numArgs == 2 ifTrue:[
-        ^ self perform:aSelector with:optionalArg1 with:optionalArg2
+	^ self perform:aSelector with:optionalArg1 with:optionalArg2
     ].
     ^ self perform:aSelector with:optionalArg1 with:optionalArg2 with:optionalArg3.
 
@@ -6650,16 +6651,16 @@
 
     numArgs := aSelector argumentCount.
     numArgs == 0 ifTrue:[
-        ^ self perform:aSelector
+	^ self perform:aSelector
     ].
     numArgs == 1 ifTrue:[
-        ^ self perform:aSelector with:optionalArg1
+	^ self perform:aSelector with:optionalArg1
     ].
     numArgs == 2 ifTrue:[
-        ^ self perform:aSelector with:optionalArg1 with:optionalArg2
+	^ self perform:aSelector with:optionalArg1 with:optionalArg2
     ].
     numArgs == 3 ifTrue:[
-        ^ self perform:aSelector with:optionalArg1 with:optionalArg2 with:optionalArg3
+	^ self perform:aSelector with:optionalArg1 with:optionalArg2 with:optionalArg3
     ].
     ^ self perform:aSelector with:optionalArg1 with:optionalArg2 with:optionalArg3 with:optionalArg4.
 
@@ -9044,11 +9045,11 @@
     "return the value of the first arg, if I am nil,
      the result from evaluating the 2nd argument, if I am not nil.
      Notice:
-        This method is open coded (inlined) by the compiler(s)
-        - redefining it may not work as expected."
+	This method is open coded (inlined) by the compiler(s)
+	- redefining it may not work as expected."
 
     (notNilBlockOrValue isBlock and:[notNilBlockOrValue argumentCount == 1]) ifTrue:[
-        ^ notNilBlockOrValue value:self.
+	^ notNilBlockOrValue value:self.
     ].
     ^ notNilBlockOrValue value
 !
@@ -9057,11 +9058,11 @@
     "return myself if nil, or the result from evaluating the argument,
      if I am not nil.
      Notice:
-        This method is open coded (inlined) by the compiler(s)
-        - redefining it may not work as expected."
+	This method is open coded (inlined) by the compiler(s)
+	- redefining it may not work as expected."
 
     (aBlockOrValue isBlock and:[aBlockOrValue argumentCount == 1]) ifTrue:[
-        ^ aBlockOrValue value:self.
+	^ aBlockOrValue value:self.
     ].
     ^ aBlockOrValue value
 !
@@ -9070,11 +9071,11 @@
     "return the value of the 2nd arg, if I am nil,
      the result from evaluating the 1st argument, if I am not nil.
      Notice:
-        This method is open coded (inlined) by the compiler(s)
-        - redefining it may not work as expected."
+	This method is open coded (inlined) by the compiler(s)
+	- redefining it may not work as expected."
 
     (notNilBlockOrValue isBlock and:[notNilBlockOrValue argumentCount == 1]) ifTrue:[
-        ^ notNilBlockOrValue value:self.
+	^ notNilBlockOrValue value:self.
     ].
     ^ notNilBlockOrValue value
 !
@@ -10301,11 +10302,11 @@
 !Object class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Object.st,v 1.809 2015-06-05 16:11:10 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Object.st,v 1.809 2015-06-05 16:11:10 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_HG
--- a/ProcessorScheduler.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/ProcessorScheduler.st	Fri Jul 24 08:06:37 2015 +0100
@@ -337,7 +337,7 @@
 	sz := KnownProcessIds size.
 	1 to:sz do:[:index |
 	    "/ (KnownProcesses at:index) isNil ifTrue:[
-	    (KnownProcesses at:index) == 0 ifTrue:[
+	    (KnownProcesses at:index) class == SmallInteger ifTrue:[
 		id := KnownProcessIds at:index.
 		id notNil ifTrue:[
 		    'Processor [warning]: terminating thread ' errorPrint.
@@ -455,14 +455,14 @@
 knownProcesses
     "return a collection of all (living) processes in the system"
 
-    ^ KnownProcesses select:[:p | p notNil and:[p ~~ 0]]
+    ^ KnownProcesses select:[:p | p notNil and:[p class ~~ SmallInteger]]
 !
 
 knownProcessesDo:aBlock
     "evaluate aBlock for each (living) processes in the system"
 
     KnownProcesses do:[:p |
-	(p notNil and:[p ~~ 0]) ifTrue:[aBlock value:p]
+	(p notNil and:[p class ~~ SmallInteger]) ifTrue:[aBlock value:p]
     ]
 
     "Created: / 26-10-2012 / 13:02:33 / cg"
@@ -1008,7 +1008,7 @@
     "
     processesToRestart := OrderedCollection new.
     KnownProcesses do:[:p |
-	(p notNil and:[p ~~ 0]) ifTrue:[
+	(p notNil and:[p class ~~ SmallInteger]) ifTrue:[
 	    "how, exactly should this be done ?"
 
 	    p isRestartable == true ifTrue:[
@@ -3564,11 +3564,11 @@
 !ProcessorScheduler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ProcessorScheduler.st,v 1.303 2015-04-27 17:04:46 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/ProcessorScheduler.st,v 1.303 2015-04-27 17:04:46 cg Exp $'
+    ^ '$Header$'
 ! !
 
 
--- a/Registry.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/Registry.st	Fri Jul 24 08:06:37 2015 +0100
@@ -36,15 +36,15 @@
 
 documentation
 "
-    Registries provide an easy interface to using WeakArrays. 
+    Registries provide an easy interface to using WeakArrays.
     A class, which wants to be informed of instance-death, can put a created object
-    into a registry. The registry will create an executor, which is a (shallow-)copy 
-    of the object, and watch out for death of the original object. When it dies, 
+    into a registry. The registry will create an executor, which is a (shallow-)copy
+    of the object, and watch out for death of the original object. When it dies,
     the executor will be sent a #finalize message.
     The trick with the shallow copy is especially nice, you can think of it as
     being the original object which died.
 
-    All objects, which keep external resources (such as fileDescriptors, fonts, 
+    All objects, which keep external resources (such as fileDescriptors, fonts,
     colormap-entries etc.) should be registered, so that the underlying resource
     can be freed when the object goes away.
 
@@ -52,8 +52,8 @@
     death of an object.
 
     Registries use #executor to aquire the copy of the original,
-    this can be redefined in individual classes for faster copying 
-    (typically, not all internal state, but only some device handles are needed for 
+    this can be redefined in individual classes for faster copying
+    (typically, not all internal state, but only some device handles are needed for
     finalization). If the to-be-registered object is large, this method may also
     return a stub (placeHolder) object. (i.e. there is no need for the copy to be
     of the same class as the original, as long as it implements #finalize and frees
@@ -62,12 +62,12 @@
     Example uses are found in Form, Color, ExternalStream and Font
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [see also:]
-        WeakArray WeakIdentityDictionary WeakIdentitySet
-        Font Form Color Cursor ExternalStream
-        
+	WeakArray WeakIdentityDictionary WeakIdentitySet
+	Font Form Color Cursor ExternalStream
+
 "
 ! !
 
@@ -102,60 +102,60 @@
      o myHandleArray wasBlocked|
 
     something == #ElementExpired ifTrue:[
-        wasBlocked := OperatingSystem blockInterrupts.
-        [
-            myHandleArray := handleArray.
-            sz := myHandleArray size.
+	wasBlocked := OperatingSystem blockInterrupts.
+	[
+	    myHandleArray := handleArray.
+	    sz := myHandleArray size.
 
-            index := 1.
-            [index <= sz] whileTrue:[
-                o := registeredObjects at:index.
-                o == 0 ifTrue:[
-                    executor := myHandleArray at:index.
-                    "remove the executor from the handle array before informing the executor.
-                     This is critical in case of errors while executing the executor.
-                     See ObjectMemory>>finalize"
-                    registeredObjects at:index put:nil.
-                    tally := tally - 1.
-                    executor notNil ifTrue:[
-                        myHandleArray at:index put:nil.
+	    index := 1.
+	    [index <= sz] whileTrue:[
+		o := registeredObjects at:index.
+		o class == SmallInteger ifTrue:[
+		    executor := myHandleArray at:index.
+		    "remove the executor from the handle array before informing the executor.
+		     This is critical in case of errors while executing the executor.
+		     See ObjectMemory>>finalize"
+		    registeredObjects at:index put:nil.
+		    tally := tally - 1.
+		    executor notNil ifTrue:[
+			myHandleArray at:index put:nil.
 
-                        "/
-                        "/ allow interrupts for a while ...
-                        "/
-                        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-                        self informDispose:executor.
-                        OperatingSystem blockInterrupts.
+			"/
+			"/ allow interrupts for a while ...
+			"/
+			wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+			self informDispose:executor.
+			OperatingSystem blockInterrupts.
 
-                        "/
-                        "/ any change in an interrupt or dispose handling ?
-                        "/
-                        handleArray ~~ myHandleArray ifTrue:[
-                            myHandleArray := handleArray.
-                            sz := myHandleArray size.
-                            "/ start again
-                            index := 0.
-                        ]
-                    ]
-                ].
-                index := index + 1.
-            ]
-        ] ensure:[
-            wasBlocked ifFalse:[
-                OperatingSystem unblockInterrupts
-            ]
-        ].
+			"/
+			"/ any change in an interrupt or dispose handling ?
+			"/
+			handleArray ~~ myHandleArray ifTrue:[
+			    myHandleArray := handleArray.
+			    sz := myHandleArray size.
+			    "/ start again
+			    index := 0.
+			]
+		    ]
+		].
+		index := index + 1.
+	    ]
+	] ensure:[
+	    wasBlocked ifFalse:[
+		OperatingSystem unblockInterrupts
+	    ]
+	].
 
-        (sz > 50 and:[tally < (sz // 2)]) ifTrue:[
-            "/ shrink
-            self resize
-        ]
+	(sz > 50 and:[tally < (sz // 2)]) ifTrue:[
+	    "/ shrink
+	    self resize
+	]
     ] ifFalse:[
-        something == #earlyRestart ifTrue:[
-            handleArray notNil ifTrue:[
-                handleArray atAllPut:nil.
-            ]
-        ]
+	something == #earlyRestart ifTrue:[
+	    handleArray notNil ifTrue:[
+		handleArray atAllPut:nil.
+	    ]
+	]
     ].
 
     "Created: 15.6.1996 / 15:24:41 / cg"
@@ -167,9 +167,9 @@
 
 detect:aBlock ifNone:exceptionValue
     registeredObjects notNil ifTrue:[
-        registeredObjects validElementsDo:[:obj |
-            (aBlock value:obj) ifTrue:[^ obj].
-        ].
+	registeredObjects validElementsDo:[:obj |
+	    (aBlock value:obj) ifTrue:[^ obj].
+	].
     ].
     ^ exceptionValue value
 !
@@ -197,14 +197,14 @@
     cnt := 0.
 
     1 to:sz do:[:index |
-        ((executor := registeredObjects at:index) notNil 
-        and:[executor ~~ 0]) ifTrue:[
-            indexTable at:executor put:index.
-            cnt := cnt + 1.
-        ] ifFalse:[
-            handleArray at:index put:nil.
-            registeredObjects at:index put:nil.
-        ]
+	((executor := registeredObjects at:index) notNil
+	and:[executor class ~~ SmallInteger]) ifTrue:[
+	    indexTable at:executor put:index.
+	    cnt := cnt + 1.
+	] ifFalse:[
+	    handleArray at:index put:nil.
+	    registeredObjects at:index put:nil.
+	]
     ].
 
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
@@ -216,45 +216,45 @@
     |sz          "{ Class: SmallInteger }"
      dstIndex    "{ Class: SmallInteger }"
      realNewSize "{ Class: SmallInteger }"
-     newObjects newHandles wasBlocked 
+     newObjects newHandles wasBlocked
      executor|
 
     sz := registeredObjects size.
 
     (sz > 50 and:[tally < (sz // 2)]) ifTrue:[
-        "/ shrink
+	"/ shrink
 
-        wasBlocked := OperatingSystem blockInterrupts.
+	wasBlocked := OperatingSystem blockInterrupts.
 
-        sz := registeredObjects size.
-        realNewSize := tally * 3 // 2.
-        newObjects := WeakArray new:realNewSize.
-        newHandles := Array new:realNewSize.
-        indexTable := WeakIdentityDictionary new.
+	sz := registeredObjects size.
+	realNewSize := tally * 3 // 2.
+	newObjects := WeakArray new:realNewSize.
+	newHandles := Array new:realNewSize.
+	indexTable := WeakIdentityDictionary new.
 
-        dstIndex := 1.
-        1 to:sz do:[:index |
-            (executor := registeredObjects at:index) notNil ifTrue:[
-                dstIndex > realNewSize ifTrue:[
-                    'Registry [error]: size given is too small in resize' errorPrintCR.
-                    self repairTally.
-                    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-                    ^ self
-                ].
-                newObjects at:dstIndex put:executor.
-                newHandles at:dstIndex put:(handleArray at:index).
-                indexTable at:executor put:dstIndex.
+	dstIndex := 1.
+	1 to:sz do:[:index |
+	    (executor := registeredObjects at:index) notNil ifTrue:[
+		dstIndex > realNewSize ifTrue:[
+		    'Registry [error]: size given is too small in resize' errorPrintCR.
+		    self repairTally.
+		    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+		    ^ self
+		].
+		newObjects at:dstIndex put:executor.
+		newHandles at:dstIndex put:(handleArray at:index).
+		indexTable at:executor put:dstIndex.
 
-                dstIndex := dstIndex + 1
-            ]
-        ].
+		dstIndex := dstIndex + 1
+	    ]
+	].
 
-        registeredObjects removeDependent:self.
-        newObjects addDependent:self.
-        registeredObjects := newObjects.
-        handleArray := newHandles.
+	registeredObjects removeDependent:self.
+	newObjects addDependent:self.
+	registeredObjects := newObjects.
+	handleArray := newHandles.
 
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ]
 
     "Created: 16.1.1997 / 18:08:00 / cg"
@@ -266,8 +266,8 @@
 
     handleArray at:index put:nil.
     registeredObjects at:index put:nil.
-    (anObject notNil and:[anObject ~~ 0]) ifTrue:[ 
-        indexTable removeKey:anObject ifAbsent:[]
+    (anObject notNil and:[anObject ~~ 0]) ifTrue:[
+	indexTable removeKey:anObject ifAbsent:[]
     ].
     tally := tally - 1.
 ! !
@@ -288,7 +288,7 @@
 
     executor := anObject executor.
     executor notNil ifTrue:[
-        self register:anObject as:executor.
+	self register:anObject as:executor.
     ].
 !
 
@@ -304,19 +304,19 @@
     wasBlocked := OperatingSystem blockInterrupts.
 
     registeredObjects size == 0 "isNil" ifTrue:[
-        registeredObjects := WeakArray new:10.
-        registeredObjects addDependent:self.
-        handleArray := Array basicNew:10.
-        indexTable := WeakIdentityDictionary new.
+	registeredObjects := WeakArray new:10.
+	registeredObjects addDependent:self.
+	handleArray := Array basicNew:10.
+	indexTable := WeakIdentityDictionary new.
 
-        registeredObjects at:1 put:anObject.
-        handleArray at:1 put:aHandle.
-        indexTable at:anObject put:1.
+	registeredObjects at:1 put:anObject.
+	handleArray at:1 put:aHandle.
+	indexTable at:anObject put:1.
 
-        tally := 1.
-        ObjectMemory addDependent:self.
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-        ^ self
+	tally := 1.
+	ObjectMemory addDependent:self.
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	^ self
     ].
 
     "/
@@ -324,24 +324,24 @@
     "/ (but continue with interrupts disabled)
     "/
     wasBlocked ifFalse:[
-        OperatingSystem unblockInterrupts.
-        OperatingSystem blockInterrupts.
+	OperatingSystem unblockInterrupts.
+	OperatingSystem blockInterrupts.
     ].
 
     "/ index := registeredObjects identityIndexOf:anObject ifAbsent:0.
     index := indexTable at:anObject ifAbsent:0.
     index ~~ 0 ifTrue:[
-        "/ double check ...
-        (registeredObjects at:index) ~~ anObject ifTrue:[
-            ('Registry [warning]: index table clobbered') errorPrintCR.
-        ].
+	"/ double check ...
+	(registeredObjects at:index) ~~ anObject ifTrue:[
+	    ('Registry [warning]: index table clobbered') errorPrintCR.
+	].
 
-        "already registered"
-        
-        handleArray at:index put:aHandle.
+	"already registered"
+
+	handleArray at:index put:aHandle.
 "/        ('Registry [info]: object (' , (registeredObjects at:index) printString , ') is already registered') infoPrintCR.
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-        ^ self
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	^ self
     ].
 
     "/
@@ -349,8 +349,8 @@
     "/ (but continue with interrupts disabled)
     "/
     wasBlocked ifFalse:[
-        OperatingSystem unblockInterrupts.
-        OperatingSystem blockInterrupts.
+	OperatingSystem unblockInterrupts.
+	OperatingSystem blockInterrupts.
     ].
 
     "/
@@ -360,26 +360,26 @@
     idx0 := 1.
     index := registeredObjects identityIndexOf:nil startingAt:idx0.
     [index ~~ 0] whileTrue:[
-        "is there a leftover ?"
-        p := handleArray at:index.
-        p isNil ifTrue:[
-            registeredObjects at:index put:anObject.
-            handleArray at:index put:aHandle.
-            indexTable at:anObject put:index.
+	"is there a leftover ?"
+	p := handleArray at:index.
+	p isNil ifTrue:[
+	    registeredObjects at:index put:anObject.
+	    handleArray at:index put:aHandle.
+	    indexTable at:anObject put:index.
 
-            tally := tally + 1.
-            wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-            ^ self
-        ].
+	    tally := tally + 1.
+	    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	    ^ self
+	].
 
-        "/ mhmh - a registeredObject vanished, but its
-        "/ executor is still there ...
+	"/ mhmh - a registeredObject vanished, but its
+	"/ executor is still there ...
 
-        "/
-        "/ this may happen, if the registries dispose handling is 
-        "/ currently being executed by a lower priority process,
-        "/ and the registeredObject has already been nilled,
-        "/ but the executor is being notified (in the other process).
+	"/
+	"/ this may happen, if the registries dispose handling is
+	"/ currently being executed by a lower priority process,
+	"/ and the registeredObject has already been nilled,
+	"/ but the executor is being notified (in the other process).
 
 "/        'Registry [info]: leftOver executor: ' infoPrint. p infoPrintCR.
 
@@ -389,8 +389,8 @@
 "/        self informDispose:p.
 "/        p := nil.
 
-        idx0 := index + 1.
-        index := registeredObjects identityIndexOf:nil startingAt:idx0.
+	idx0 := index + 1.
+	index := registeredObjects identityIndexOf:nil startingAt:idx0.
     ].
 
     "no free slot, add at the end"
@@ -425,21 +425,21 @@
 
     executor := anObject executor.
     executor isNil ifTrue:[
-        self unregister:anObject.
-        ^ self.
+	self unregister:anObject.
+	^ self.
     ].
 
     wasBlocked := OperatingSystem blockInterrupts.
     registeredObjects isNil ifTrue:[
-        index := 0
+	index := 0
     ] ifFalse:[
-        "/ index := registeredObjects identityIndexOf:anObject ifAbsent:0.
-        index := indexTable at:anObject ifAbsent:0.
+	"/ index := registeredObjects identityIndexOf:anObject ifAbsent:0.
+	index := indexTable at:anObject ifAbsent:0.
     ].
     index ~~ 0 ifTrue:[
-        handleArray at:index put:executor.
+	handleArray at:index put:executor.
     ] ifFalse:[
-        self register:anObject as:executor
+	self register:anObject as:executor
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 
@@ -454,15 +454,15 @@
     |index wasBlocked|
 
     registeredObjects notNil ifTrue:[
-        wasBlocked := OperatingSystem blockInterrupts.
-        "/ index := registeredObjects identityIndexOf:anObject ifAbsent:0.
-        index := indexTable at:anObject ifAbsent:0.
-        index ~~ 0 ifTrue:[
-            self unregister:anObject atIndex:index.
-        ].
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	wasBlocked := OperatingSystem blockInterrupts.
+	"/ index := registeredObjects identityIndexOf:anObject ifAbsent:0.
+	index := indexTable at:anObject ifAbsent:0.
+	index ~~ 0 ifTrue:[
+	    self unregister:anObject atIndex:index.
+	].
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 
-        self resize
+	self resize
     ]
 
     "Modified: 16.1.1997 / 18:08:42 / cg"
@@ -484,7 +484,7 @@
 
 	1 to:n do:[:index |
 	    obj := registeredObjects at:index.
-	    (obj notNil and:[obj ~~ 0]) ifTrue:[
+	    (obj notNil and:[obj class ~~ SmallInteger]) ifTrue:[
 		(aBlock value:obj) ifTrue:[
 		    self unregister:obj atIndex:index.
 		    any := true.
@@ -526,10 +526,10 @@
 !Registry class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Registry.st,v 1.64 2013-06-03 18:02:40 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Registry.st,v 1.64 2013-06-03 18:02:40 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/String.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/String.st	Fri Jul 24 08:06:37 2015 +0100
@@ -2370,7 +2370,9 @@
 
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
-    return context._RETURN( STSymbol.asSymbolIfInterned( self.asString() ));
+    STObject symbolOrNull = STSymbol.asSymbolIfInterned( self.asString() );
+
+    return context._RETURN( symbolOrNull == null ? STObject.Nil : symbolOrNull );
 #else
     OBJ cls;
     int indx;
--- a/Symbol.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/Symbol.st	Fri Jul 24 08:06:37 2015 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -59,7 +61,7 @@
 	which is a symbol consisting of the user visible name, prefixed by ':<ns>::'.
 	The VM's method lookup algorithm contains special handling code for such constructs.
 	Thus, if two methods are stored as 'foo' and ':NS::foo' are present in a class,
-	any send of 'foo' from wíthin the NS-namespace will invoke the second method.
+	any send of 'foo' from wíthin the NS-namespace will invoke the second method.
 	Any other send will invoke the first one.
 
 
@@ -274,9 +276,8 @@
 nameSpace
     "if I have the format of a namespace-selector,
      retrieve the namespace. Otherwise, return nil.
-     Also return nil, if that namespace does not exist.
-     Namespace selectors have a special, fix defined format, which
-     is also known in the VM.
+     Also return nil, if that namespace does not exist (in contrast to nameSpacePart).
+     Namespace selectors have a special, fix defined format, which is also known in the VM.
      They must be of the form :<ns>::<sel>,
      where <ns> is the namespace and <sel> is the raw selector.
      This special format (a symbol starting with a colon) was chosen, because almost every other selector
@@ -284,15 +285,16 @@
 
      |nsPart|
 
-     self isNameSpaceSelector ifFalse:[^ nil].
-
      nsPart := self nameSpaceAndSelectorParts first.
+     nsPart isNil ifTrue:[^ nil].
      ^ Smalltalk at:nsPart asSymbol
 
     "
      #':foo:' nameSpace       -> nil (bad format)
      #':foo::bar' nameSpace   -> nil (non existing)
      #':Tools::bar' nameSpace -> Tools
+     #'bar' nameSpace -> nil
+     #'bar:' nameSpace -> nil
     "
 
     "Created: / 20-07-2010 / 10:41:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -302,8 +304,7 @@
     "return a two element tuple consisting of the namespace and the raw selector.
      If I do not have the format of a namespace-selector, or the namespace is non-existing,
      the first element of the returned tuple will be nil.
-     Namespace selectors have a special, fix defined format, which
-     is also known in the VM.
+     Namespace selectors have a special, fix defined format, which is also known in the VM.
      They must be of the form :<ns>::<sel>,
      where <ns> is the namespace and <sel> is the raw selector.
      This special format (a symbol starting with a colon) was chosen, because almost every other selector
@@ -312,7 +313,7 @@
     |parts ns|
 
     self isNameSpaceSelector ifFalse:[
-	^ Array with:nil with:self
+        ^ Array with:nil with:self
     ].
     parts := self nameSpaceAndSelectorParts.
     ns := Smalltalk at:parts first asSymbol.
@@ -329,10 +330,9 @@
 
 nameSpaceAndSelectorParts
     "return a two element tuple consisting of the namespace name and the raw selector.
-     If I do not have the format of a namespace-selector, or the namespace is non-existing,
+     If I do not have the format of a namespace-selector, 
      the first element of the returned tuple will be nil.
-     Namespace selectors have a special, fix defined format, which
-     is also known in the VM.
+     Namespace selectors have a special, fix defined format, which is also known in the VM.
      They must be of the form :<ns>::<sel>,
      where <ns> is the namespace and <sel> is the raw selector.
      This special format (a symbol starting with a colon) was chosen, because almost every other selector
@@ -341,7 +341,7 @@
      |nsPart selPart idx|
 
     self isNameSpaceSelector ifFalse:[
-	^ Array with:nil with:self
+        ^ Array with:nil with:self
     ].
     idx := self indexOf:$: startingAt:3.
     nsPart := self copyFrom:2 to:idx - 1.
@@ -349,9 +349,17 @@
     ^ Array with:nsPart with:selPart asSymbol
 
     "
-     #':foo:bar' nameSpaceAndSelector     -> #(nil #':foo:bar')
-     #':foo::bar' nameSpaceAndSelector    -> #(nil #bar)
-     #':Tools::foo' nameSpaceAndSelector  -> #(Tools (* NameSpace *) #foo)
+     #':foo:bar' nameSpaceAndSelectorParts     -> #(nil #':foo:bar')
+     #':foo:bar' nameSpaceAndSelector          -> #(nil #':foo:bar')
+
+     #':foo::bar' nameSpaceAndSelectorParts    -> #('foo' #bar)
+     #':foo::bar' nameSpaceAndSelector         -> #(nil #bar)
+
+     #'bar' nameSpaceAndSelectorParts          -> #(nil #bar)
+     #'bar' nameSpaceAndSelector               -> #(nil #bar)
+
+     #':Tools::foo' nameSpaceAndSelectorParts  -> #('Tools' #foo)
+     #':Tools::foo' nameSpaceAndSelector       -> #(Tools (* NameSpace *) #foo)
     "
 
     "Created: / 20-07-2010 / 10:23:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -360,14 +368,12 @@
 nameSpacePart
     "if I have the format of a namespace-selector,
      retrieve the namespace name. Otherwise, return nil.
-     Namespace selectors have a special, fix defined format,
-     which is also known in the VM.
+     Namespace selectors have a special, fix defined format, which is also known in the VM.
      They must be of the form :<ns>::<sel>,
      where <ns> is the namespace and <sel> is the raw selector.
      This special format (a symbol starting with a colon) was chosen, because almost every other selector
      is legal, and this can be checked quickly by just looking at the first character."
 
-     self isNameSpaceSelector ifFalse:[^ nil].
      ^ self nameSpaceAndSelectorParts first.
 
     "
@@ -401,9 +407,7 @@
      This special format (a symbol starting with a colon) was chosen, because almost every other selector
      is legal, and this can be checked quickly by just looking at the first character."
 
-     ^ self isNameSpaceSelector
-	ifTrue: [ self nameSpaceAndSelectorParts second ]
-	ifFalse:[ self ]
+     ^ self nameSpaceAndSelectorParts second
 
     "
      #':foo:' selectorWithoutNameSpace       -> #':foo:' (bad format)
@@ -879,11 +883,11 @@
 !Symbol class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Symbol.st,v 1.117 2015-05-18 00:06:52 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Symbol.st,v 1.117 2015-05-18 00:06:52 cg Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/UnixOperatingSystem.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/UnixOperatingSystem.st	Fri Jul 24 08:06:37 2015 +0100
@@ -2,7 +2,7 @@
 
 "
  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
@@ -16,90 +16,90 @@
 "{ NameSpace: Smalltalk }"
 
 AbstractOperatingSystem subclass:#UnixOperatingSystem
-	instanceVariableNames:''
-	classVariableNames:'Initialized HostName DomainName SlowFork ForkFailed
-		CurrentDirectory LastTimeInfo LastTimeInfoSeconds
-		LastTimeInfoMilliseconds LastTimeInfoIsLocal CachedMountPoints
-		CacheMountPointsTimeStamp Codeset CodesetEncoder'
-	poolDictionaries:''
-	category:'OS-Unix'
+        instanceVariableNames:''
+        classVariableNames:'Initialized HostName DomainName SlowFork ForkFailed
+                CurrentDirectory LastTimeInfo LastTimeInfoSeconds
+                LastTimeInfoMilliseconds LastTimeInfoIsLocal CachedMountPoints
+                CacheMountPointsTimeStamp Codeset CodesetEncoder'
+        poolDictionaries:''
+        category:'OS-Unix'
 !
 
 SharedPool subclass:#ELFConstants
-	instanceVariableNames:''
-	classVariableNames:'EI_MAG0 ELFMAG0 EI_MAG1 ELFMAG1 EI_MAG2 ELFMAG2 EI_MAG3 ELFMAG3
-		EI_CLASS ELFCLASSNONE ELFCLASS32 ELFCLASS64 ELFCLASSNUM EI_DATA
-		ELFDATANONE ELFDATA2LSB ELFDATA2MSB ELFDATANUM EI_VERSION
-		EI_OSABI ELFOSABI_NONE ELFOSABI_SYSV ELFOSABI_HPUX
-		ELFOSABI_NETBSD ELFOSABI_GNU ELFOSABI_LINUX ELFOSABI_SOLARIS
-		ELFOSABI_AIX ELFOSABI_IRIX ELFOSABI_FREEBSD ELFOSABI_TRU64
-		ELFOSABI_MODESTO ELFOSABI_OPENBSD ELFOSABI_ARM_AEABI ELFOSABI_ARM
-		ELFOSABI_STANDALONE EI_ABIVERSION EI_PAD ET_NONE ET_REL ET_EXEC
-		ET_DYN ET_CORE ET_LOOS ET_HIOS ET_LOPROC ET_HIPROC EM_NONE EM_M32
-		EM_SPARC EM_386 EM_68K EM_88K EM_860 EM_MIPS EM_S370
-		EM_MIPS_RS3_LE EM_PARISC EM_VPP500 EM_SPARC32PLUS EM_960 EM_PPC
-		EM_PPC64 EM_S390 EM_V800 EM_FR20 EM_RH32 EM_RCE EM_ARM
-		EM_FAKE_ALPHA EM_SH EM_SPARCV9 EM_TRICORE EM_ARC EM_H8_300
-		EM_H8_300H EM_H8S EM_H8_500 EM_IA_64 EM_MIPS_X EM_COLDFIRE
-		EM_68HC12 EM_MMA EM_PCP EM_NCPU EM_NDR1 EM_STARCORE EM_ME16
-		EM_ST100 EM_TINYJ EM_X86_64 EM_PDSP EM_FX66 EM_ST9PLUS EM_ST7
-		EM_68HC16 EM_68HC11 EM_68HC08 EM_68HC05 EM_SVX EM_ST19 EM_VAX
-		EM_CRIS EM_JAVELIN EM_FIREPATH EM_ZSP EM_MMIX EM_HUANY EM_PRISM
-		EM_AVR EM_FR30 EM_D10V EM_D30V EM_V850 EM_M32R EM_MN10300
-		EM_MN10200 EM_PJ EM_OPENRISC EM_ARC_A5 EM_XTENSA EM_AARCH64
-		EM_TILEPRO EM_MICROBLAZE EM_TILEGX EM_ALPHA EV_NONE EV_CURRENT'
-	poolDictionaries:''
-	privateIn:UnixOperatingSystem
+        instanceVariableNames:''
+        classVariableNames:'EI_MAG0 ELFMAG0 EI_MAG1 ELFMAG1 EI_MAG2 ELFMAG2 EI_MAG3 ELFMAG3
+                EI_CLASS ELFCLASSNONE ELFCLASS32 ELFCLASS64 ELFCLASSNUM EI_DATA
+                ELFDATANONE ELFDATA2LSB ELFDATA2MSB ELFDATANUM EI_VERSION
+                EI_OSABI ELFOSABI_NONE ELFOSABI_SYSV ELFOSABI_HPUX
+                ELFOSABI_NETBSD ELFOSABI_GNU ELFOSABI_LINUX ELFOSABI_SOLARIS
+                ELFOSABI_AIX ELFOSABI_IRIX ELFOSABI_FREEBSD ELFOSABI_TRU64
+                ELFOSABI_MODESTO ELFOSABI_OPENBSD ELFOSABI_ARM_AEABI ELFOSABI_ARM
+                ELFOSABI_STANDALONE EI_ABIVERSION EI_PAD ET_NONE ET_REL ET_EXEC
+                ET_DYN ET_CORE ET_LOOS ET_HIOS ET_LOPROC ET_HIPROC EM_NONE EM_M32
+                EM_SPARC EM_386 EM_68K EM_88K EM_860 EM_MIPS EM_S370
+                EM_MIPS_RS3_LE EM_PARISC EM_VPP500 EM_SPARC32PLUS EM_960 EM_PPC
+                EM_PPC64 EM_S390 EM_V800 EM_FR20 EM_RH32 EM_RCE EM_ARM
+                EM_FAKE_ALPHA EM_SH EM_SPARCV9 EM_TRICORE EM_ARC EM_H8_300
+                EM_H8_300H EM_H8S EM_H8_500 EM_IA_64 EM_MIPS_X EM_COLDFIRE
+                EM_68HC12 EM_MMA EM_PCP EM_NCPU EM_NDR1 EM_STARCORE EM_ME16
+                EM_ST100 EM_TINYJ EM_X86_64 EM_PDSP EM_FX66 EM_ST9PLUS EM_ST7
+                EM_68HC16 EM_68HC11 EM_68HC08 EM_68HC05 EM_SVX EM_ST19 EM_VAX
+                EM_CRIS EM_JAVELIN EM_FIREPATH EM_ZSP EM_MMIX EM_HUANY EM_PRISM
+                EM_AVR EM_FR30 EM_D10V EM_D30V EM_V850 EM_M32R EM_MN10300
+                EM_MN10200 EM_PJ EM_OPENRISC EM_ARC_A5 EM_XTENSA EM_AARCH64
+                EM_TILEPRO EM_MICROBLAZE EM_TILEGX EM_ALPHA EV_NONE EV_CURRENT'
+        poolDictionaries:''
+        privateIn:UnixOperatingSystem
 !
 
 Object subclass:#ELFFileHeader
-	instanceVariableNames:'file data msb'
-	classVariableNames:''
-	poolDictionaries:'UnixOperatingSystem::ELFConstants'
-	privateIn:UnixOperatingSystem
+        instanceVariableNames:'file data msb'
+        classVariableNames:''
+        poolDictionaries:'UnixOperatingSystem::ELFConstants'
+        privateIn:UnixOperatingSystem
 !
 
 Object subclass:#FileDescriptorHandle
-	instanceVariableNames:'fd'
-	classVariableNames:'OpenFiles'
-	poolDictionaries:''
-	privateIn:UnixOperatingSystem
+        instanceVariableNames:'fd'
+        classVariableNames:'OpenFiles'
+        poolDictionaries:''
+        privateIn:UnixOperatingSystem
 !
 
 OSFileHandle subclass:#FilePointerHandle
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:UnixOperatingSystem
+        instanceVariableNames:''
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:UnixOperatingSystem
 !
 
 Object subclass:#FileStatusInfo
-	instanceVariableNames:'type mode uid gid size id accessed modified statusChanged
-		sourcePath targetPath numLinks'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:UnixOperatingSystem
+        instanceVariableNames:'type mode uid gid size id accessed modified statusChanged
+                sourcePath targetPath numLinks'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:UnixOperatingSystem
 !
 
 Object subclass:#MountInfo
-	instanceVariableNames:'mountPointPath deviceOrRemotePath fsType attributeString'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:UnixOperatingSystem
+        instanceVariableNames:'mountPointPath deviceOrRemotePath fsType attributeString'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:UnixOperatingSystem
 !
 
 Object subclass:#OSProcessStatus
-	instanceVariableNames:'pid status code core'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:UnixOperatingSystem
+        instanceVariableNames:'pid status code core'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:UnixOperatingSystem
 !
 
 UnixOperatingSystem::FilePointerHandle subclass:#SocketHandle
-	instanceVariableNames:''
-	classVariableNames:'ProtocolCache'
-	poolDictionaries:''
-	privateIn:UnixOperatingSystem
+        instanceVariableNames:''
+        classVariableNames:'ProtocolCache'
+        poolDictionaries:''
+        privateIn:UnixOperatingSystem
 !
 
 !UnixOperatingSystem primitiveDefinitions!
@@ -285,6 +285,7 @@
 
 # ifdef __osx__
 #  include <string.h>
+#  include <stdlib.h>
 #  include <time.h>
 #  ifndef _TIME_H_
 /* hack if the osx has been configured with case-ignoring filenames,
@@ -299,17 +300,17 @@
 #   ifndef _TIME_H_
 // old hack
 struct tm {
-	int     tm_sec;         /* seconds after the minute [0-60] */
-	int     tm_min;         /* minutes after the hour [0-59] */
-	int     tm_hour;        /* hours since midnight [0-23] */
-	int     tm_mday;        /* day of the month [1-31] */
-	int     tm_mon;         /* months since January [0-11] */
-	int     tm_year;        /* years since 1900 */
-	int     tm_wday;        /* days since Sunday [0-6] */
-	int     tm_yday;        /* days since January 1 [0-365] */
-	int     tm_isdst;       /* Daylight Savings Time flag */
-	long    tm_gmtoff;      /* offset from CUT in seconds */
-	char    *tm_zone;       /* timezone abbreviation */
+        int     tm_sec;         /* seconds after the minute [0-60] */
+        int     tm_min;         /* minutes after the hour [0-59] */
+        int     tm_hour;        /* hours since midnight [0-23] */
+        int     tm_mday;        /* day of the month [1-31] */
+        int     tm_mon;         /* months since January [0-11] */
+        int     tm_year;        /* years since 1900 */
+        int     tm_wday;        /* days since Sunday [0-6] */
+        int     tm_yday;        /* days since January 1 [0-365] */
+        int     tm_isdst;       /* Daylight Savings Time flag */
+        long    tm_gmtoff;      /* offset from CUT in seconds */
+        char    *tm_zone;       /* timezone abbreviation */
 };
 #   endif
 #  endif /* NO_LONGER */
@@ -697,103 +698,103 @@
     sigset_t block, omask;
 
     if (line == NULL)
-	return -1;
+        return -1;
 
     sa.sa_handler = SIG_IGN;
     sa.sa_flags = 0;
     __sigemptyset (&sa.sa_mask);
 
     if (__sigaction (SIGINT, &sa, &intr) < 0) {
-	DPRINTF(("1: errno=%d\n", errno));
-	return -1;
+        DPRINTF(("1: errno=%d\n", errno));
+        return -1;
     }
     if (__sigaction (SIGQUIT, &sa, &quit) < 0) {
-	save = errno;
-	(void) __sigaction (SIGINT, &intr, (struct sigaction *) NULL);
-	errno = save;
-	DPRINTF(("2: errno=%d\n", errno));
-	return -1;
+        save = errno;
+        (void) __sigaction (SIGINT, &intr, (struct sigaction *) NULL);
+        errno = save;
+        DPRINTF(("2: errno=%d\n", errno));
+        return -1;
     }
 
     __sigemptyset (&block);
     __sigaddset (&block, SIGCHLD);
     save = errno;
     if (__sigprocmask(SIG_BLOCK, &block, &omask) < 0) {
-	if (errno == ENOSYS)
-	    errno = save;
-	else {
-	    save = errno;
-	    (void) __sigaction(SIGINT, &intr, (struct sigaction *) NULL);
-	    (void) __sigaction (SIGQUIT, &quit, (struct sigaction *) NULL);
-	    errno = save;
-	    DPRINTF(("3: errno=%d\n", errno));
-	    return -1;
-	}
+        if (errno == ENOSYS)
+            errno = save;
+        else {
+            save = errno;
+            (void) __sigaction(SIGINT, &intr, (struct sigaction *) NULL);
+            (void) __sigaction (SIGQUIT, &quit, (struct sigaction *) NULL);
+            errno = save;
+            DPRINTF(("3: errno=%d\n", errno));
+            return -1;
+        }
     }
 
     pid = FORK ();
     if (pid == (pid_t) 0) {
-	/* Child side.  */
-	CONST char *new_argv[4];
-	new_argv[0] = SHELL_NAME;
-	new_argv[1] = "-c";
-	new_argv[2] = line;
-	new_argv[3] = NULL;
-
-	/* Restore the signals.  */
-	(void) __sigaction (SIGINT, &intr, (struct sigaction *) NULL);
-	(void) __sigaction (SIGQUIT, &quit, (struct sigaction *) NULL);
-	(void) __sigprocmask (SIG_SETMASK, &omask, (sigset_t *) NULL);
-
-	/* Exec the shell.  */
-	(void) __execve (SHELL_PATH, (char *CONST *) new_argv, __environ);
-	_exit (127);
+        /* Child side.  */
+        CONST char *new_argv[4];
+        new_argv[0] = SHELL_NAME;
+        new_argv[1] = "-c";
+        new_argv[2] = line;
+        new_argv[3] = NULL;
+
+        /* Restore the signals.  */
+        (void) __sigaction (SIGINT, &intr, (struct sigaction *) NULL);
+        (void) __sigaction (SIGQUIT, &quit, (struct sigaction *) NULL);
+        (void) __sigprocmask (SIG_SETMASK, &omask, (sigset_t *) NULL);
+
+        /* Exec the shell.  */
+        (void) __execve (SHELL_PATH, (char *CONST *) new_argv, __environ);
+        _exit (127);
     } else {
-	if (pid < (pid_t) 0) {
-	    /* The fork failed.  */
-	    DPRINTF(("4: errno=%d\n", errno));
-	    status = -1;
-	} else {
-	    /* Parent side.  */
+        if (pid < (pid_t) 0) {
+            /* The fork failed.  */
+            DPRINTF(("4: errno=%d\n", errno));
+            status = -1;
+        } else {
+            /* Parent side.  */
 #ifdef  NO_WAITPID
-	    pid_t child;
-
-	    do {
-		__BEGIN_INTERRUPTABLE__
-		child = __wait (&status);
-		__END_INTERRUPTABLE__
-		if (child < 0 && errno != EINTR) {
-		    DPRINTF(("5: errno=%d\n", errno));
-		    status = -1;
-		    break;
-		}
-	    } while (child != pid);
+            pid_t child;
+
+            do {
+                __BEGIN_INTERRUPTABLE__
+                child = __wait (&status);
+                __END_INTERRUPTABLE__
+                if (child < 0 && errno != EINTR) {
+                    DPRINTF(("5: errno=%d\n", errno));
+                    status = -1;
+                    break;
+                }
+            } while (child != pid);
 #else
-	    pid_t child;
-
-	    /* claus: the original did not care for EINTR here ... */
-	    do {
-		__BEGIN_INTERRUPTABLE__
-		child = __waitpid (pid, &status, 0);
-		__END_INTERRUPTABLE__
-	    } while ((child != pid) && (errno == EINTR));
-	    if (child != pid) {
-		DPRINTF(("6: errno=%d\n", errno));
-		status = -1;
-	    }
+            pid_t child;
+
+            /* claus: the original did not care for EINTR here ... */
+            do {
+                __BEGIN_INTERRUPTABLE__
+                child = __waitpid (pid, &status, 0);
+                __END_INTERRUPTABLE__
+            } while ((child != pid) && (errno == EINTR));
+            if (child != pid) {
+                DPRINTF(("6: errno=%d\n", errno));
+                status = -1;
+            }
 #endif /* NO_WAITPID */
-	}
+        }
     }
     save = errno;
     if ((__sigaction (SIGINT, &intr, (struct sigaction *) NULL)
      | __sigaction (SIGQUIT, &quit, (struct sigaction *) NULL)
      | __sigprocmask (SIG_SETMASK, &omask, (sigset_t *) NULL)) != 0) {
-	if (errno == ENOSYS) {
-	    errno = save;
-	} else {
-	    status = -1;
-	    DPRINTF(("7: errno=%d\n", errno));
-	}
+        if (errno == ENOSYS) {
+            errno = save;
+        } else {
+            status = -1;
+            DPRINTF(("7: errno=%d\n", errno));
+        }
     }
 
     return status;
@@ -832,123 +833,123 @@
 static char *
 realpath(const char *path, char *resolved_path)
 {
-	char copy_path[MAXPATHLEN];
-	char link_path[MAXPATHLEN];
-	char *new_path, *max_path, *mallocedPath;
-	int readlinks = 0;
-	int n;
-
-	if (resolved_path == NULL) {
-	    mallocedPath = resolved_path = malloc(MAXPATHLEN+1);
-	}
-	new_path = resolved_path;
-
-	/* Make a copy of the source path since we may need to modify it. */
-	strcpy(copy_path, path);
-	path = copy_path;
-	max_path = copy_path + MAXPATHLEN - 2;
-	/* If it's a relative pathname use getwd for starters. */
-	if (*path != '/') {
+        char copy_path[MAXPATHLEN];
+        char link_path[MAXPATHLEN];
+        char *new_path, *max_path, *mallocedPath;
+        int readlinks = 0;
+        int n;
+
+        if (resolved_path == NULL) {
+            mallocedPath = resolved_path = malloc(MAXPATHLEN+1);
+        }
+        new_path = resolved_path;
+
+        /* Make a copy of the source path since we may need to modify it. */
+        strcpy(copy_path, path);
+        path = copy_path;
+        max_path = copy_path + MAXPATHLEN - 2;
+        /* If it's a relative pathname use getwd for starters. */
+        if (*path != '/') {
 #ifdef HAS_GETCWD
-		new_path = getcwd(new_path, MAXPATHLEN - 1);
+                new_path = getcwd(new_path, MAXPATHLEN - 1);
 #else
-		new_path = getwd(new_path);
-#endif
-		if (new_path == NULL) {
-		    if (mallocedPath) free(mallocedPath);
-		    return(NULL);
-		}
-
-		new_path += strlen(new_path);
-		if (new_path[-1] != '/')
-			*new_path++ = '/';
-	}
-	else {
-		*new_path++ = '/';
-		path++;
-	}
-	/* Expand each slash-separated pathname component. */
-	while (*path != '\0') {
-		/* Ignore stray "/". */
-		if (*path == '/') {
-			path++;
-			continue;
-		}
-		if (*path == '.') {
-			/* Ignore ".". */
-			if (path[1] == '\0' || path[1] == '/') {
-				path++;
-				continue;
-			}
-			if (path[1] == '.') {
-				if (path[2] == '\0' || path[2] == '/') {
-					path += 2;
-					/* Ignore ".." at root. */
-					if (new_path == resolved_path + 1)
-						continue;
-					/* Handle ".." by backing up. */
-					while ((--new_path)[-1] != '/')
-						;
-					continue;
-				}
-			}
-		}
-		/* Safely copy the next pathname component. */
-		while (*path != '\0' && *path != '/') {
-			if (path > max_path) {
-			    if (mallocedPath) free(mallocedPath);
-			    errno = ENAMETOOLONG;
-			    return NULL;
-			}
-			*new_path++ = *path++;
-		}
+                new_path = getwd(new_path);
+#endif
+                if (new_path == NULL) {
+                    if (mallocedPath) free(mallocedPath);
+                    return(NULL);
+                }
+
+                new_path += strlen(new_path);
+                if (new_path[-1] != '/')
+                        *new_path++ = '/';
+        }
+        else {
+                *new_path++ = '/';
+                path++;
+        }
+        /* Expand each slash-separated pathname component. */
+        while (*path != '\0') {
+                /* Ignore stray "/". */
+                if (*path == '/') {
+                        path++;
+                        continue;
+                }
+                if (*path == '.') {
+                        /* Ignore ".". */
+                        if (path[1] == '\0' || path[1] == '/') {
+                                path++;
+                                continue;
+                        }
+                        if (path[1] == '.') {
+                                if (path[2] == '\0' || path[2] == '/') {
+                                        path += 2;
+                                        /* Ignore ".." at root. */
+                                        if (new_path == resolved_path + 1)
+                                                continue;
+                                        /* Handle ".." by backing up. */
+                                        while ((--new_path)[-1] != '/')
+                                                ;
+                                        continue;
+                                }
+                        }
+                }
+                /* Safely copy the next pathname component. */
+                while (*path != '\0' && *path != '/') {
+                        if (path > max_path) {
+                            if (mallocedPath) free(mallocedPath);
+                            errno = ENAMETOOLONG;
+                            return NULL;
+                        }
+                        *new_path++ = *path++;
+                }
 #ifdef S_IFLNK
-		/* Protect against infinite loops. */
-		if (readlinks++ > MAX_READLINKS) {
-		    if (mallocedPath) free(mallocedPath);
-		    errno = ELOOP;
-		    return NULL;
-		}
-		/* See if latest pathname component is a symlink. */
-		*new_path = '\0';
-		n = readlink(resolved_path, link_path, MAXPATHLEN - 1);
-		if (n < 0) {
-			/* EINVAL means the file exists but isn't a symlink. */
-			if (errno != EINVAL) {
-			    if (mallocedPath) free(mallocedPath);
-			    return NULL;
-			}
-		}
-		else {
-			/* Note: readlink doesn't add the null byte. */
-			link_path[n] = '\0';
-			if (*link_path == '/')
-				/* Start over for an absolute symlink. */
-				new_path = resolved_path;
-			else
-				/* Otherwise back up over this component. */
-				while (*(--new_path) != '/')
-					;
-			/* Safe sex check. */
-			if (strlen(path) + n >= MAXPATHLEN) {
-			    if (mallocedPath) free(mallocedPath);
-			    errno = ENAMETOOLONG;
-			    return NULL;
-			}
-			/* Insert symlink contents into path. */
-			strcat(link_path, path);
-			strcpy(copy_path, link_path);
-			path = copy_path;
-		}
+                /* Protect against infinite loops. */
+                if (readlinks++ > MAX_READLINKS) {
+                    if (mallocedPath) free(mallocedPath);
+                    errno = ELOOP;
+                    return NULL;
+                }
+                /* See if latest pathname component is a symlink. */
+                *new_path = '\0';
+                n = readlink(resolved_path, link_path, MAXPATHLEN - 1);
+                if (n < 0) {
+                        /* EINVAL means the file exists but isn't a symlink. */
+                        if (errno != EINVAL) {
+                            if (mallocedPath) free(mallocedPath);
+                            return NULL;
+                        }
+                }
+                else {
+                        /* Note: readlink doesn't add the null byte. */
+                        link_path[n] = '\0';
+                        if (*link_path == '/')
+                                /* Start over for an absolute symlink. */
+                                new_path = resolved_path;
+                        else
+                                /* Otherwise back up over this component. */
+                                while (*(--new_path) != '/')
+                                        ;
+                        /* Safe sex check. */
+                        if (strlen(path) + n >= MAXPATHLEN) {
+                            if (mallocedPath) free(mallocedPath);
+                            errno = ENAMETOOLONG;
+                            return NULL;
+                        }
+                        /* Insert symlink contents into path. */
+                        strcat(link_path, path);
+                        strcpy(copy_path, link_path);
+                        path = copy_path;
+                }
 #endif /* S_IFLNK */
-		*new_path++ = '/';
-	}
-	/* Delete trailing slash but don't whomp a lone slash. */
-	if (new_path != resolved_path + 1 && new_path[-1] == '/')
-		new_path--;
-	/* Make sure it's null terminated. */
-	*new_path = '\0';
-	return resolved_path;
+                *new_path++ = '/';
+        }
+        /* Delete trailing slash but don't whomp a lone slash. */
+        if (new_path != resolved_path + 1 && new_path[-1] == '/')
+                new_path--;
+        /* Make sure it's null terminated. */
+        *new_path = '\0';
+        return resolved_path;
 }
 # define HAS_REALPATH
 #endif /* WANT_REALPATH && not HAS_REALPATH */
@@ -961,7 +962,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
@@ -986,93 +987,93 @@
 
     [Class variables:]
 
-	HostName        <String>        remembered hostname
-
-	DomainName      <String>        remembered domainname
-
-	SlowFork        <Boolean>       if set, fork and popen are avoided;
-					(more or less obsolete now)
-
-
-	CurrentDirectory <String>       remembered currentDirectories path
+        HostName        <String>        remembered hostname
+
+        DomainName      <String>        remembered domainname
+
+        SlowFork        <Boolean>       if set, fork and popen are avoided;
+                                        (more or less obsolete now)
+
+
+        CurrentDirectory <String>       remembered currentDirectories path
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 
     [see also:]
-	OSProcessStatus
-	Filename Date Time
-	ExternalStream FileStream PipeStream Socket
+        OSProcessStatus
+        Filename Date Time
+        ExternalStream FileStream PipeStream Socket
 "
 !
 
 examples
 "
   various queries
-								[exBegin]
+                                                                [exBegin]
     Transcript
-	showCR:'hello ' , (OperatingSystem getLoginName)
-								[exEnd]
-
-								[exBegin]
+        showCR:'hello ' , (OperatingSystem getLoginName)
+                                                                [exEnd]
+
+                                                                [exBegin]
     OperatingSystem isUNIXlike ifTrue:[
-	Transcript showCR:'this is some UNIX-like OS'
+        Transcript showCR:'this is some UNIX-like OS'
     ] ifFalse:[
-	Transcript showCR:'this OS is not UNIX-like'
+        Transcript showCR:'this OS is not UNIX-like'
     ]
-								[exEnd]
-
-								[exBegin]
+                                                                [exEnd]
+
+                                                                [exBegin]
     Transcript
-	showCR:'this machine is called ' , OperatingSystem getHostName
-								[exEnd]
-
-								[exBegin]
+        showCR:'this machine is called ' , OperatingSystem getHostName
+                                                                [exEnd]
+
+                                                                [exBegin]
     Transcript
-	showCR:('this machine is in the '
-	       , OperatingSystem getDomainName
-	       , ' domain')
-								[exEnd]
-
-								[exBegin]
+        showCR:('this machine is in the '
+               , OperatingSystem getDomainName
+               , ' domain')
+                                                                [exEnd]
+
+                                                                [exBegin]
     Transcript
-	showCR:('this machine''s CPU is a '
-	       , OperatingSystem getCPUType
-	       )
-								[exEnd]
-
-								[exBegin]
+        showCR:('this machine''s CPU is a '
+               , OperatingSystem getCPUType
+               )
+                                                                [exEnd]
+
+                                                                [exBegin]
     Transcript showCR:'executing ls command ...'.
     OperatingSystem executeCommand:'ls'.
     Transcript showCR:'... done.'.
-								[exEnd]
+                                                                [exEnd]
 
   locking a file
   (should be executed on two running smalltalks - not in two threads):
-								[exBegin]
+                                                                [exBegin]
     |f|
 
     f := 'testFile' asFilename readWriteStream.
 
     10 timesRepeat:[
-	'about to lock ...' printCR.
-	[
-	  OperatingSystem
-	    lockFD:(f fileDescriptor)
-	    shared:false
-	    blocking:false
-	] whileFalse:[
-	    'process ' print. OperatingSystem getProcessId print. ' is waiting' printCR.
-	    Delay waitForSeconds:1
-	].
-	'LOCKED ...' printCR.
-	Delay waitForSeconds:10.
-	'unlock ...' printCR.
-	(OperatingSystem
-	    unlockFD:(f fileDescriptor)) printCR.
-	Delay waitForSeconds:3.
+        'about to lock ...' printCR.
+        [
+          OperatingSystem
+            lockFD:(f fileDescriptor)
+            shared:false
+            blocking:false
+        ] whileFalse:[
+            'process ' print. OperatingSystem getProcessId print. ' is waiting' printCR.
+            Delay waitForSeconds:1
+        ].
+        'LOCKED ...' printCR.
+        Delay waitForSeconds:10.
+        'unlock ...' printCR.
+        (OperatingSystem
+            unlockFD:(f fileDescriptor)) printCR.
+        Delay waitForSeconds:3.
     ]
-								[exBegin]
+                                                                [exBegin]
 "
 ! !
 
@@ -1083,9 +1084,9 @@
 
     "/ protect against double initialization
     Initialized isNil ifTrue:[
-	ObjectMemory addDependent:self.
-	self initializeCachedData.
-	Initialized := true.
+        ObjectMemory addDependent:self.
+        self initializeCachedData.
+        Initialized := true.
     ].
 !
 
@@ -1114,16 +1115,16 @@
     setlocale(LC_CTYPE, "");
     __codeset = nl_langinfo(CODESET);
     if (strlen(__codeset) > 0) {
-	codeset = __MKSTRING(__codeset);
+        codeset = __MKSTRING(__codeset);
     }
 %}.
     codeset notNil ifTrue:[
-	codeset := codeset asLowercase.
-	codeset = 'utf-8' ifTrue:[
-	    codeset := #utf8.
-	] ifFalse:[
-	    codeset := codeset asSymbol.
-	].
+        codeset := codeset asLowercase.
+        codeset = 'utf-8' ifTrue:[
+            codeset := #utf8.
+        ] ifFalse:[
+            codeset := codeset asSymbol.
+        ].
     ].
     Codeset := codeset.
     ^ codeset.
@@ -1137,7 +1138,7 @@
     "catch image restart and flush some cached data"
 
     something == #earlyRestart ifTrue:[
-	self initializeCachedData
+        self initializeCachedData
     ]
 
     "Created: / 15.6.1996 / 15:22:37 / cg"
@@ -1639,230 +1640,230 @@
 %{  /* NOCONTEXT */
 #ifdef SIGABRT
     if (signalName == @symbol(SIGABRT)) {
-	RETURN ( __mkSmallInteger(SIGABRT) );
+        RETURN ( __mkSmallInteger(SIGABRT) );
     }
 #endif
 #ifdef SIGALRM
     if (signalName == @symbol(SIGALRM)) {
-	RETURN ( __mkSmallInteger(SIGALRM) );
+        RETURN ( __mkSmallInteger(SIGALRM) );
     }
 #endif
 #ifdef SIGBREAK
     if (signalName == @symbol(SIGBREAK)) {
-	RETURN ( __mkSmallInteger(SIGBREAK) );
+        RETURN ( __mkSmallInteger(SIGBREAK) );
     }
 #endif
 #ifdef SIGBUS
     if (signalName == @symbol(SIGBUS)) {
-	RETURN ( __mkSmallInteger(SIGBUS) );
+        RETURN ( __mkSmallInteger(SIGBUS) );
     }
 #endif
 #ifdef SIGCHLD
     if ((signalName == @symbol(SIGCHLD))
      || (signalName == @symbol(SIGCLD)) ) {
-	RETURN ( __mkSmallInteger(SIGCHLD) );
+        RETURN ( __mkSmallInteger(SIGCHLD) );
     }
 #else
 # if defined(SIGCLD)
     if ((signalName == @symbol(SIGCHLD))
      || (signalName == @symbol(SIGCLD)) ) {
-	RETURN ( __mkSmallInteger(SIGCLD) );
+        RETURN ( __mkSmallInteger(SIGCLD) );
     }
 # endif
 #endif
 #ifdef SIGCONT
     if (signalName == @symbol(SIGCONT)) {
-	RETURN ( __mkSmallInteger(SIGCONT) );
+        RETURN ( __mkSmallInteger(SIGCONT) );
     }
 #endif
 #ifdef SIGDANGER
     if (signalName == @symbol(SIGDANGER)) {
-	RETURN ( __mkSmallInteger(SIGDANGER) );
+        RETURN ( __mkSmallInteger(SIGDANGER) );
     }
 #endif
 #ifdef SIGEMT
     if (signalName == @symbol(SIGEMT)) {
-	RETURN ( __mkSmallInteger(SIGEMT) );
+        RETURN ( __mkSmallInteger(SIGEMT) );
     }
 #endif
 #ifdef SIGFPE
     if (signalName == @symbol(SIGFPE)) {
-	RETURN ( __mkSmallInteger(SIGFPE) );
+        RETURN ( __mkSmallInteger(SIGFPE) );
     }
 #endif
 #ifdef SIGGRANT
     if (signalName == @symbol(SIGGRANT)) {
-	RETURN ( __mkSmallInteger(SIGGRANT) );
+        RETURN ( __mkSmallInteger(SIGGRANT) );
     }
 #endif
 #ifdef SIGHUP
     if (signalName == @symbol(SIGHUP)) {
-	RETURN ( __mkSmallInteger(SIGHUP) );
+        RETURN ( __mkSmallInteger(SIGHUP) );
     }
 #endif
 #ifdef SIGILL
     if (signalName == @symbol(SIGILL)) {
-	RETURN ( __mkSmallInteger(SIGILL) );
+        RETURN ( __mkSmallInteger(SIGILL) );
     }
 #endif
 #ifdef SIGINT
     if (signalName == @symbol(SIGINT)) {
-	RETURN ( __mkSmallInteger(SIGINT) );
+        RETURN ( __mkSmallInteger(SIGINT) );
     }
 #endif
 #ifdef SIGIO
     if (signalName == @symbol(SIGIO)) {
-	RETURN ( __mkSmallInteger(SIGIO) );
+        RETURN ( __mkSmallInteger(SIGIO) );
     }
 #endif
 #ifdef SIGIOT
     if (signalName == @symbol(SIGIOT)) {
-	RETURN ( __mkSmallInteger(SIGIOT) );
+        RETURN ( __mkSmallInteger(SIGIOT) );
     }
 #endif
 #ifdef SIGKILL
     if (signalName == @symbol(SIGKILL)) {
-	RETURN ( __mkSmallInteger(SIGKILL) );
+        RETURN ( __mkSmallInteger(SIGKILL) );
     }
 #endif
 #ifdef SIGLOST
     if (signalName == @symbol(SIGLOST)) {
-	RETURN ( __mkSmallInteger(SIGLOST) );
+        RETURN ( __mkSmallInteger(SIGLOST) );
     }
 #endif
 #ifdef SIGMIGRATE
     if (signalName == @symbol(SIGMIGRATE)) {
-	RETURN ( __mkSmallInteger(SIGMIGRATE) );
+        RETURN ( __mkSmallInteger(SIGMIGRATE) );
     }
 #endif
 #ifdef SIGMSG
     if (signalName == @symbol(SIGMSG)) {
-	RETURN ( __mkSmallInteger(SIGMSG) );
+        RETURN ( __mkSmallInteger(SIGMSG) );
     }
 #endif
 #ifdef SIGPIPE
     if (signalName == @symbol(SIGPIPE)) {
-	RETURN ( __mkSmallInteger(SIGPIPE) );
+        RETURN ( __mkSmallInteger(SIGPIPE) );
     }
 #endif
 #ifdef SIGPOLL
     if (signalName == @symbol(SIGPOLL)) {
-	RETURN ( __mkSmallInteger(SIGPOLL) );
+        RETURN ( __mkSmallInteger(SIGPOLL) );
     }
 #endif
 #ifdef SIGPRE
     if (signalName == @symbol(SIGPRE)) {
-	RETURN ( __mkSmallInteger(SIGPRE) );
+        RETURN ( __mkSmallInteger(SIGPRE) );
     }
 #endif
 #ifdef SIGPROF
     if (signalName == @symbol(SIGPROF)) {
-	RETURN ( __mkSmallInteger(SIGPROF) );
+        RETURN ( __mkSmallInteger(SIGPROF) );
     }
 #endif
 #ifdef SIGPWR
     if (signalName == @symbol(SIGPWR)) {
-	RETURN ( __mkSmallInteger(SIGPWR) );
+        RETURN ( __mkSmallInteger(SIGPWR) );
     }
 #endif
 #ifdef SIGQUIT
     if (signalName == @symbol(SIGQUIT)) {
-	RETURN ( __mkSmallInteger(SIGQUIT) );
+        RETURN ( __mkSmallInteger(SIGQUIT) );
     }
 #endif
 #ifdef SIGRETRACT
     if (signalName == @symbol(SIGRETRACT)) {
-	RETURN ( __mkSmallInteger(SIGRETRACT) );
+        RETURN ( __mkSmallInteger(SIGRETRACT) );
     }
 #endif
 #ifdef SIGSAK
     if (signalName == @symbol(SIGSAK)) {
-	RETURN ( __mkSmallInteger(SIGSAK) );
+        RETURN ( __mkSmallInteger(SIGSAK) );
     }
 #endif
 #ifdef SIGSEGV
     if (signalName == @symbol(SIGSEGV)) {
-	RETURN ( __mkSmallInteger(SIGSEGV) );
+        RETURN ( __mkSmallInteger(SIGSEGV) );
     }
 #endif
 #ifdef SIGSOUND
     if (signalName == @symbol(SIGSOUND)) {
-	RETURN ( __mkSmallInteger(SIGSOUND) );
+        RETURN ( __mkSmallInteger(SIGSOUND) );
     }
 #endif
 #ifdef SIGSTOP
     if (signalName == @symbol(SIGSTOP)) {
-	RETURN ( __mkSmallInteger(SIGSTOP) );
+        RETURN ( __mkSmallInteger(SIGSTOP) );
     }
 #endif
 #ifdef SIGSYS
     if (signalName == @symbol(SIGSYS)) {
-	RETURN ( __mkSmallInteger(SIGSYS) );
+        RETURN ( __mkSmallInteger(SIGSYS) );
     }
 #endif
 #ifdef SIGTERM
     if (signalName == @symbol(SIGTERM)) {
-	RETURN ( __mkSmallInteger(SIGTERM) );
+        RETURN ( __mkSmallInteger(SIGTERM) );
     }
 #endif
 #ifdef SIGTRAP
     if (signalName == @symbol(SIGTRAP)) {
-	RETURN ( __mkSmallInteger(SIGTRAP) );
+        RETURN ( __mkSmallInteger(SIGTRAP) );
     }
 #endif
 #ifdef SIGTSTP
     if (signalName == @symbol(SIGTSTP)) {
-	RETURN ( __mkSmallInteger(SIGTSTP) );
+        RETURN ( __mkSmallInteger(SIGTSTP) );
     }
 #endif
 #ifdef SIGTTIN
     if (signalName == @symbol(SIGTTIN)) {
-	RETURN ( __mkSmallInteger(SIGTTIN) );
+        RETURN ( __mkSmallInteger(SIGTTIN) );
     }
 #endif
 #ifdef SIGTTOU
     if (signalName == @symbol(SIGTTOU)) {
-	RETURN ( __mkSmallInteger(SIGTTOU) );
+        RETURN ( __mkSmallInteger(SIGTTOU) );
     }
 #endif
 #ifdef SIGURG
     if (signalName == @symbol(SIGURG)) {
-	RETURN ( __mkSmallInteger(SIGURG) );
+        RETURN ( __mkSmallInteger(SIGURG) );
     }
 #endif
 #ifdef SIGUSR1
     if (signalName == @symbol(SIGUSR1)) {
-	RETURN ( __mkSmallInteger(SIGUSR1) );
+        RETURN ( __mkSmallInteger(SIGUSR1) );
     }
 #endif
 #ifdef SIGUSR2
     if (signalName == @symbol(SIGUSR2)) {
-	RETURN ( __mkSmallInteger(SIGUSR2) );
+        RETURN ( __mkSmallInteger(SIGUSR2) );
     }
 #endif
 #ifdef SIGVTALRM
     if (signalName == @symbol(SIGVTALRM)) {
-	RETURN ( __mkSmallInteger(SIGVTALRM) );
+        RETURN ( __mkSmallInteger(SIGVTALRM) );
     }
 #endif
 #ifdef SIGWINCH
     if (signalName == @symbol(SIGWINCH)) {
-	RETURN ( __mkSmallInteger(SIGWINCH) );
+        RETURN ( __mkSmallInteger(SIGWINCH) );
     }
 #endif
 #ifdef SIGXCPU
     if (signalName == @symbol(SIGXCPU)) {
-	RETURN ( __mkSmallInteger(SIGXCPU) );
+        RETURN ( __mkSmallInteger(SIGXCPU) );
     }
 #endif
 #ifdef SIGXFSZ
     if (signalName == @symbol(SIGXFSZ)) {
-	RETURN ( __mkSmallInteger(SIGXFSZ) );
+        RETURN ( __mkSmallInteger(SIGXFSZ) );
     }
 #endif
 #ifdef SIGINFO
     if (signalName == @symbol(SIGINFO)) {
-	RETURN ( __mkSmallInteger(SIGINFO) );
+        RETURN ( __mkSmallInteger(SIGINFO) );
     }
 #endif
 %}.
@@ -1884,7 +1885,7 @@
 %{
 #ifdef HAS_OPENDIR
     if (__isExternalAddressLike(dirPointer)) {
-	closedir( (DIR *)(__FILEVal(dirPointer)) );
+        closedir( (DIR *)(__FILEVal(dirPointer)) );
     }
 #endif
 %}.
@@ -1906,41 +1907,41 @@
 
     if ((dirPointer != nil)
      && __isExternalAddressLike(dirPointer)) {
-	d = (DIR *)__FILEVal(dirPointer);
-
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    do {
-		__threadErrno = 0;
-		dp = readdir(d);
-		/*
-		 * for compatibility with ST-80,
-		 * skip entries for '.' and '..'.
-		 * If wanted, these must be added synthetically.
-		 */
-	    } while (dp && ((strcmp(dp->d_name, ".")==0) || (strcmp(dp->d_name, "..")==0)));
-	} while ((dp == NULL) && (__threadErrno == EINTR));
-	__END_INTERRUPTABLE__
-
-	if (dp != NULL) {
-	    entry = __MKSTRING((char *)(dp->d_name));
-	} else {
-	    if (__threadErrno) {
-		error = __mkSmallInteger(__threadErrno);
-	    }
+        d = (DIR *)__FILEVal(dirPointer);
+
+        __BEGIN_INTERRUPTABLE__
+        do {
+            do {
+                __threadErrno = 0;
+                dp = readdir(d);
+                /*
+                 * for compatibility with ST-80,
+                 * skip entries for '.' and '..'.
+                 * If wanted, these must be added synthetically.
+                 */
+            } while (dp && ((strcmp(dp->d_name, ".")==0) || (strcmp(dp->d_name, "..")==0)));
+        } while ((dp == NULL) && (__threadErrno == EINTR));
+        __END_INTERRUPTABLE__
+
+        if (dp != NULL) {
+            entry = __MKSTRING((char *)(dp->d_name));
+        } else {
+            if (__threadErrno) {
+                error = __mkSmallInteger(__threadErrno);
+            }
        }
     }
 #endif /* HAS_OPENDIR */
 %}.
     error notNil ifTrue:[
-	^ StreamIOError newException
-	    errorCode:error;
-	    osErrorHolder:(OperatingSystem errorHolderForNumber:error);
-	    parameter:aDirectoryStream;
-	    raiseRequest
+        ^ StreamIOError newException
+            errorCode:error;
+            osErrorHolder:(OperatingSystem errorHolderForNumber:error);
+            parameter:aDirectoryStream;
+            raiseRequest
     ].
     entry notNil ifTrue:[
-	^ FileStatusInfo new sourcePath:(self decodePath:entry).
+        ^ FileStatusInfo new sourcePath:(self decodePath:entry).
     ].
     ^ aDirectoryStream pastEndRead
 ! !
@@ -1951,9 +1952,9 @@
     "open a windows-shell/mac finder/desktop application to present the document contained in aFilenameOrString.
      This is typically used to present help-files, html documents, pdf documents etc.
      operationSymbol is one of:
-	open
-	edit
-	explore
+        open
+        edit
+        explore
      mimeTypeStringArgOrNil is e.g. 'text/html' or: 'application/pdf';
      if nil is passed in, the file's suffix is used to guess it.
     "
@@ -1962,16 +1963,16 @@
 
     cmd := self openApplicationHelperCommand.
     cmd notNil ifTrue:[
-	(cmd includesSubString:'%1') ifTrue:[
-	    cmd := cmd bindWith:aFilenameOrString asString.
-	] ifFalse:[
-	    cmd := cmd, ' "', aFilenameOrString asString, '"'.
-	].
-	(self
-		startProcess:cmd
-		inputFrom:nil outputTo:nil
-		errorTo:nil auxFrom:nil
-		environment: self getEnvironment inDirectory:nil) notNil ifTrue:[ ^ self ]
+        (cmd includesSubString:'%1') ifTrue:[
+            cmd := cmd bindWith:aFilenameOrString asString.
+        ] ifFalse:[
+            cmd := cmd, ' "', aFilenameOrString asString, '"'.
+        ].
+        (self
+                startProcess:cmd
+                inputFrom:nil outputTo:nil
+                errorTo:nil auxFrom:nil
+                environment: self getEnvironment inDirectory:nil) notNil ifTrue:[ ^ self ]
     ].
     ^ super openApplicationForDocument:aFilenameOrString operation:operationSymbol mimeType:mimeTypeStringArgOrNil ifNone:exceptionBlock
 
@@ -1994,14 +1995,14 @@
 
     xdgCurrentDesktop := self getEnvironment: 'XDG_CURRENT_DESKTOP'.
     ((xdgCurrentDesktop = 'GNOME') and:[self canExecuteCommand: 'gnome-open']) ifTrue:[
-	^ 'gnome-open'
+        ^ 'gnome-open'
     ].
     "/ Guess...
     ((xdgCurrentDesktop = 'KDE') and:[self canExecuteCommand: 'kde-open']) ifTrue:[
-	^ 'kde-open'
+        ^ 'kde-open'
     ].
     (self canExecuteCommand: 'xdg-open') ifTrue:[
-	^ 'xdg-open'
+        ^ 'xdg-open'
     ].
     ^ nil
 
@@ -2049,530 +2050,530 @@
      */
 
     if (__isSmallInteger(errNr)) {
-	switch ( __intVal(errNr)) {
-	    /*
-	     * POSIX errnos - these should be defined
-	     */
+        switch ( __intVal(errNr)) {
+            /*
+             * POSIX errnos - these should be defined
+             */
 #ifdef EPERM
-	    case EPERM:
-		sym = @symbol(EPERM);
-		typ = @symbol(noPermissionsSignal);
-		break;
+            case EPERM:
+                sym = @symbol(EPERM);
+                typ = @symbol(noPermissionsSignal);
+                break;
 #endif
 #ifdef ENOENT
-	    case ENOENT:
-		sym = @symbol(ENOENT);
-		typ = @symbol(nonexistentSignal);
-		break;
+            case ENOENT:
+                sym = @symbol(ENOENT);
+                typ = @symbol(nonexistentSignal);
+                break;
 #endif
 #ifdef ESRCH
-	    case ESRCH:
-		sym = @symbol(ESRCH);
-		typ = @symbol(unavailableReferentSignal);
-		break;
+            case ESRCH:
+                sym = @symbol(ESRCH);
+                typ = @symbol(unavailableReferentSignal);
+                break;
 #endif
 #ifdef EINTR
-	    case EINTR:
-		sym = @symbol(EINTR);
-		typ = @symbol(transientErrorSignal);
-		break;
+            case EINTR:
+                sym = @symbol(EINTR);
+                typ = @symbol(transientErrorSignal);
+                break;
 #endif
 #ifdef EIO
-	    case EIO:
-		sym = @symbol(EIO);
-		typ = @symbol(transferFaultSignal);
-		break;
+            case EIO:
+                sym = @symbol(EIO);
+                typ = @symbol(transferFaultSignal);
+                break;
 #endif
 #ifdef ENXIO
-	    case ENXIO:
-		sym = @symbol(ENXIO);
-		typ = @symbol(unavailableReferentSignal);
-		break;
+            case ENXIO:
+                sym = @symbol(ENXIO);
+                typ = @symbol(unavailableReferentSignal);
+                break;
 #endif
 #ifdef E2BIG
-	    case E2BIG:
-		sym = @symbol(E2BIG);
-		typ = @symbol(invalidArgumentsSignal);
-		break;
+            case E2BIG:
+                sym = @symbol(E2BIG);
+                typ = @symbol(invalidArgumentsSignal);
+                break;
 #endif
 #ifdef ENOEXEC
-	    case ENOEXEC:
-		sym = @symbol(ENOEXEC);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
+            case ENOEXEC:
+                sym = @symbol(ENOEXEC);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
 #endif
 #ifdef EBADF
-	    case EBADF:
-		sym = @symbol(EBADF);
-		typ = @symbol(badAccessorSignal);
-		break;
+            case EBADF:
+                sym = @symbol(EBADF);
+                typ = @symbol(badAccessorSignal);
+                break;
 #endif
 #ifdef ECHILD
-	    case ECHILD:
-		sym = @symbol(ECHILD);
-		typ = @symbol(informationSignal);
-		break;
+            case ECHILD:
+                sym = @symbol(ECHILD);
+                typ = @symbol(informationSignal);
+                break;
 #endif
 #if !defined(EWOULDBLOCK) && defined(EAGAIN) && (EWOULDBLOCK != EAGAIN)
-	    case EAGAIN:
-		sym = @symbol(EAGAIN);
-		typ = @symbol(notReadySignal);
-		break;
+            case EAGAIN:
+                sym = @symbol(EAGAIN);
+                typ = @symbol(notReadySignal);
+                break;
 #endif
 #ifdef EOVERFLOW
-	    case EOVERFLOW:
-		sym = @symbol(EOVERFLOW);
-		typ = @symbol(rangeErrorSignal);
-		break;
+            case EOVERFLOW:
+                sym = @symbol(EOVERFLOW);
+                typ = @symbol(rangeErrorSignal);
+                break;
 #endif
 #ifdef ENOMEM
-	    case ENOMEM:
-		sym = @symbol(ENOMEM);
-		typ = @symbol(noMemorySignal);
-		break;
+            case ENOMEM:
+                sym = @symbol(ENOMEM);
+                typ = @symbol(noMemorySignal);
+                break;
 #endif
 #ifdef EACCES
-	    case EACCES:
-		sym = @symbol(EACCES);
-		typ = @symbol(noPermissionsSignal);
-		break;
+            case EACCES:
+                sym = @symbol(EACCES);
+                typ = @symbol(noPermissionsSignal);
+                break;
 #endif
 #ifdef EFAULT
-	    case EFAULT:
-		sym = @symbol(EFAULT);
-		typ = @symbol(invalidArgumentsSignal);
-		break;
+            case EFAULT:
+                sym = @symbol(EFAULT);
+                typ = @symbol(invalidArgumentsSignal);
+                break;
 #endif
 #ifdef EBUSY
-	    case EBUSY:
-		sym = @symbol(EBUSY);
-		typ = @symbol(unavailableReferentSignal);
-		break;
+            case EBUSY:
+                sym = @symbol(EBUSY);
+                typ = @symbol(unavailableReferentSignal);
+                break;
 #endif
 #ifdef EEXIST
-	    case EEXIST:
-		sym = @symbol(EEXIST);
-		typ = @symbol(existingReferentSignal);
-		break;
+            case EEXIST:
+                sym = @symbol(EEXIST);
+                typ = @symbol(existingReferentSignal);
+                break;
 #endif
 #ifdef EXDEV
-	    case EXDEV:
-		sym = @symbol(EXDEV);
-		typ = @symbol(inappropriateReferentSignal);
-		break;
+            case EXDEV:
+                sym = @symbol(EXDEV);
+                typ = @symbol(inappropriateReferentSignal);
+                break;
 #endif
 #ifdef ENODEV
-	    case ENODEV:
-		sym = @symbol(ENODEV);
-		typ = @symbol(inaccessibleSignal);
-		break;
+            case ENODEV:
+                sym = @symbol(ENODEV);
+                typ = @symbol(inaccessibleSignal);
+                break;
 #endif
 #ifdef ENOTDIR
-	    case ENOTDIR:
-		sym = @symbol(ENOTDIR);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
+            case ENOTDIR:
+                sym = @symbol(ENOTDIR);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
 #endif
 #ifdef EISDIR
-	    case EISDIR:
-		sym = @symbol(EISDIR);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
+            case EISDIR:
+                sym = @symbol(EISDIR);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
 #endif
 #ifdef EINVAL
-	    case EINVAL:
-		sym = @symbol(EINVAL);
-		typ = @symbol(invalidArgumentsSignal);
-		break;
+            case EINVAL:
+                sym = @symbol(EINVAL);
+                typ = @symbol(invalidArgumentsSignal);
+                break;
 #endif
 #ifdef ENFILE
-	    case ENFILE:
-		sym = @symbol(ENFILE);
-		typ = @symbol(noResourcesSignal);
-		break;
+            case ENFILE:
+                sym = @symbol(ENFILE);
+                typ = @symbol(noResourcesSignal);
+                break;
 #endif
 #ifdef EMFILE
-	    case EMFILE:
-		sym = @symbol(EMFILE);
-		typ = @symbol(noResourcesSignal);
-		break;
+            case EMFILE:
+                sym = @symbol(EMFILE);
+                typ = @symbol(noResourcesSignal);
+                break;
 #endif
 #ifdef ENOTTY
-	    case ENOTTY:
-		sym = @symbol(ENOTTY);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
+            case ENOTTY:
+                sym = @symbol(ENOTTY);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
 #endif
 #ifdef EFBIG
-	    case EFBIG:
-		sym = @symbol(EFBIG);
-		typ = @symbol(noResourcesSignal);
-		break;
+            case EFBIG:
+                sym = @symbol(EFBIG);
+                typ = @symbol(noResourcesSignal);
+                break;
 #endif
 #ifdef ENOSPC
-	    case ENOSPC:
-		sym = @symbol(ENOSPC);
-		typ = @symbol(noResourcesSignal);
-		break;
+            case ENOSPC:
+                sym = @symbol(ENOSPC);
+                typ = @symbol(noResourcesSignal);
+                break;
 #endif
 #ifdef ENOTSUP
 # if !defined(EOPNOTSUPP) || (ENOTSUP != EOPNOTSUPP)
-	    case ENOTSUP:
-		sym = @symbol(ENOTSUP);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
+            case ENOTSUP:
+                sym = @symbol(ENOTSUP);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
 # endif
 #endif
 #ifdef ESPIPE
-	    case ESPIPE:
-		sym = @symbol(ESPIPE);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
+            case ESPIPE:
+                sym = @symbol(ESPIPE);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
 #endif
 #ifdef EROFS
-	    case EROFS:
-		sym = @symbol(EROFS);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
+            case EROFS:
+                sym = @symbol(EROFS);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
 #endif
 #ifdef EMLINK
-	    case EMLINK:
-		sym = @symbol(EMLINK);
-		typ = @symbol(rangeErrorSignal);
-		break;
+            case EMLINK:
+                sym = @symbol(EMLINK);
+                typ = @symbol(rangeErrorSignal);
+                break;
 #endif
 #ifdef EPIPE
-	    case EPIPE:
-		sym = @symbol(EPIPE);
-		typ = @symbol(peerFaultSignal);
-		break;
+            case EPIPE:
+                sym = @symbol(EPIPE);
+                typ = @symbol(peerFaultSignal);
+                break;
 #endif
 #ifdef EDOM
-	    case EDOM:
-		sym = @symbol(EDOM);
-		typ = @symbol(rangeErrorSignal);
-		break;
+            case EDOM:
+                sym = @symbol(EDOM);
+                typ = @symbol(rangeErrorSignal);
+                break;
 #endif
 #ifdef ERANGE
-	    case ERANGE:
-		sym = @symbol(ERANGE);
-		typ = @symbol(rangeErrorSignal);
-		break;
+            case ERANGE:
+                sym = @symbol(ERANGE);
+                typ = @symbol(rangeErrorSignal);
+                break;
 #endif
 #ifdef EDEADLK
 # if EDEADLK != EWOULDBLOCK
-	    case EDEADLK:
-		sym = @symbol(EDEADLK);
-		typ = @symbol(noResourcesSignal);
-		break;
+            case EDEADLK:
+                sym = @symbol(EDEADLK);
+                typ = @symbol(noResourcesSignal);
+                break;
 # endif
 #endif
 #ifdef ENAMETOOLONG
-	    case ENAMETOOLONG:
-		sym = @symbol(ENAMETOOLONG);
-		typ = @symbol(rangeErrorSignal);
-		break;
+            case ENAMETOOLONG:
+                sym = @symbol(ENAMETOOLONG);
+                typ = @symbol(rangeErrorSignal);
+                break;
 #endif
 #ifdef ENOLCK
-	    case ENOLCK:
-		sym = @symbol(ENOLCK);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
+            case ENOLCK:
+                sym = @symbol(ENOLCK);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
 #endif
 #ifdef ENOSYS
-	    case ENOSYS:
-		sym = @symbol(ENOSYS);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
+            case ENOSYS:
+                sym = @symbol(ENOSYS);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
 #endif
 #if defined(ENOTEMPTY) && (ENOTEMPTY != EEXIST)
-	    case ENOTEMPTY:
-		sym = @symbol(ENOTEMPTY);
-		typ = @symbol(inappropriateReferentSignal);
-		break;
+            case ENOTEMPTY:
+                sym = @symbol(ENOTEMPTY);
+                typ = @symbol(inappropriateReferentSignal);
+                break;
 #endif
 #ifdef EILSEQ
-	    case EILSEQ:
-		sym = @symbol(EILSEQ);
-		typ = @symbol(transferFaultSignal);
-		break;
-#endif
-	    /*
-	     * XPG3 errnos - defined on most systems
-	     */
+            case EILSEQ:
+                sym = @symbol(EILSEQ);
+                typ = @symbol(transferFaultSignal);
+                break;
+#endif
+            /*
+             * XPG3 errnos - defined on most systems
+             */
 #ifdef ENOTBLK
-	    case ENOTBLK:
-		sym = @symbol(ENOTBLK);
-		typ = @symbol(inappropriateReferentSignal);
-		break;
+            case ENOTBLK:
+                sym = @symbol(ENOTBLK);
+                typ = @symbol(inappropriateReferentSignal);
+                break;
 #endif
 #ifdef ETXTBSY
-	    case ETXTBSY:
-		sym = @symbol(ETXTBSY);
-		typ = @symbol(inaccessibleSignal);
-		break;
-#endif
-	    /*
-	     * some others
-	     */
+            case ETXTBSY:
+                sym = @symbol(ETXTBSY);
+                typ = @symbol(inaccessibleSignal);
+                break;
+#endif
+            /*
+             * some others
+             */
 #ifdef EWOULDBLOCK
-	    case EWOULDBLOCK:
-		sym = @symbol(EWOULDBLOCK);
-		typ = @symbol(notReadySignal);
-		break;
+            case EWOULDBLOCK:
+                sym = @symbol(EWOULDBLOCK);
+                typ = @symbol(notReadySignal);
+                break;
 #endif
 #ifdef ENOMSG
-	    case ENOMSG:
-		sym = @symbol(ENOMSG);
-		typ = @symbol(noDataSignal);
-		break;
+            case ENOMSG:
+                sym = @symbol(ENOMSG);
+                typ = @symbol(noDataSignal);
+                break;
 #endif
 #ifdef ELOOP
-	    case ELOOP:
-		sym = @symbol(ELOOP);
-		typ = @symbol(rangeErrorSignal);
-		break;
-#endif
-
-	    /*
-	     * some stream errors
-	     */
+            case ELOOP:
+                sym = @symbol(ELOOP);
+                typ = @symbol(rangeErrorSignal);
+                break;
+#endif
+
+            /*
+             * some stream errors
+             */
 #ifdef ETIME
-	    case ETIME:
-		sym = @symbol(ETIME);
-		typ = @symbol(peerFaultSignal);
-		break;
+            case ETIME:
+                sym = @symbol(ETIME);
+                typ = @symbol(peerFaultSignal);
+                break;
 #endif
 #ifdef ENOSR
-	    case ENOSR:
-		sym = @symbol(ENOSR);
-		typ = @symbol(noResourcesSignal);
-		break;
+            case ENOSR:
+                sym = @symbol(ENOSR);
+                typ = @symbol(noResourcesSignal);
+                break;
 #endif
 #ifdef ENOSTR
-	    case ENOSTR:
-		sym = @symbol(ENOSTR);
-		typ = @symbol(inappropriateReferentSignal);
-		break;
+            case ENOSTR:
+                sym = @symbol(ENOSTR);
+                typ = @symbol(inappropriateReferentSignal);
+                break;
 #endif
 #ifdef ECOMM
-	    case ECOMM:
-		sym = @symbol(ECOMM);
-		typ = @symbol(transferFaultSignal);
-		break;
+            case ECOMM:
+                sym = @symbol(ECOMM);
+                typ = @symbol(transferFaultSignal);
+                break;
 #endif
 #ifdef EPROTO
-	    case EPROTO:
-		sym = @symbol(EPROTO);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
-#endif
-	    /*
-	     * nfs errors
-	     */
+            case EPROTO:
+                sym = @symbol(EPROTO);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
+#endif
+            /*
+             * nfs errors
+             */
 #ifdef ESTALE
-	    case ESTALE:
-		sym = @symbol(ESTALE);
-		typ = @symbol(unavailableReferentSignal);
-		break;
+            case ESTALE:
+                sym = @symbol(ESTALE);
+                typ = @symbol(unavailableReferentSignal);
+                break;
 #endif
 #ifdef EREMOTE
-	    case EREMOTE:
-		sym = @symbol(EREMOTE);
-		typ = @symbol(rangeErrorSignal);
-		break;
-#endif
-	    /*
-	     * some networking errors
-	     */
+            case EREMOTE:
+                sym = @symbol(EREMOTE);
+                typ = @symbol(rangeErrorSignal);
+                break;
+#endif
+            /*
+             * some networking errors
+             */
 #ifdef EINPROGRESS
-	    case EINPROGRESS:
-		sym = @symbol(EINPROGRESS);
-		typ = @symbol(operationStartedSignal);
-		break;
+            case EINPROGRESS:
+                sym = @symbol(EINPROGRESS);
+                typ = @symbol(operationStartedSignal);
+                break;
 #endif
 #ifdef EALREADY
-	    case EALREADY:
-		sym = @symbol(EALREADY);
-		typ = @symbol(operationStartedSignal);
-		break;
+            case EALREADY:
+                sym = @symbol(EALREADY);
+                typ = @symbol(operationStartedSignal);
+                break;
 #endif
 #ifdef ENOTSOCK
-	    case ENOTSOCK:
-		sym = @symbol(ENOTSOCK);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
+            case ENOTSOCK:
+                sym = @symbol(ENOTSOCK);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
 #endif
 #ifdef EDESTADDRREQ
-	    case EDESTADDRREQ:
-		sym = @symbol(EDESTADDRREQ);
-		typ = @symbol(underspecifiedSignal);
-		break;
+            case EDESTADDRREQ:
+                sym = @symbol(EDESTADDRREQ);
+                typ = @symbol(underspecifiedSignal);
+                break;
 #endif
 #ifdef EMSGSIZE
-	    case EMSGSIZE:
-		sym = @symbol(EMSGSIZE);
-		typ = @symbol(rangeErrorSignal);
-		break;
+            case EMSGSIZE:
+                sym = @symbol(EMSGSIZE);
+                typ = @symbol(rangeErrorSignal);
+                break;
 #endif
 #ifdef EPROTOTYPE
-	    case EPROTOTYPE:
-		sym = @symbol(EPROTOTYPE);
-		typ = @symbol(wrongSubtypeForOperationSignal);
-		break;
+            case EPROTOTYPE:
+                sym = @symbol(EPROTOTYPE);
+                typ = @symbol(wrongSubtypeForOperationSignal);
+                break;
 #endif
 #ifdef ENOPROTOOPT
-	    case ENOPROTOOPT:
-		sym = @symbol(ENOPROTOOPT);
-		typ = @symbol(unsupportedOperationSignal);
-		break;
+            case ENOPROTOOPT:
+                sym = @symbol(ENOPROTOOPT);
+                typ = @symbol(unsupportedOperationSignal);
+                break;
 #endif
 #ifdef EPROTONOSUPPORT
-	    case EPROTONOSUPPORT:
-		sym = @symbol(EPROTONOSUPPORT);
-		typ = @symbol(unsupportedOperationSignal);
-		break;
+            case EPROTONOSUPPORT:
+                sym = @symbol(EPROTONOSUPPORT);
+                typ = @symbol(unsupportedOperationSignal);
+                break;
 #endif
 #ifdef ESOCKTNOSUPPORT
-	    case ESOCKTNOSUPPORT:
-		sym = @symbol(ESOCKTNOSUPPORT);
-		typ = @symbol(unsupportedOperationSignal);
-		break;
+            case ESOCKTNOSUPPORT:
+                sym = @symbol(ESOCKTNOSUPPORT);
+                typ = @symbol(unsupportedOperationSignal);
+                break;
 #endif
 #ifdef EOPNOTSUPP
-	    case EOPNOTSUPP:
-		sym = @symbol(EOPNOTSUPP);
-		typ = @symbol(inappropriateOperationSignal);
-		break;
+            case EOPNOTSUPP:
+                sym = @symbol(EOPNOTSUPP);
+                typ = @symbol(inappropriateOperationSignal);
+                break;
 #endif
 #ifdef EPFNOSUPPORT
-	    case EPFNOSUPPORT:
-		sym = @symbol(EPFNOSUPPORT);
-		typ = @symbol(unsupportedOperationSignal);
-		break;
+            case EPFNOSUPPORT:
+                sym = @symbol(EPFNOSUPPORT);
+                typ = @symbol(unsupportedOperationSignal);
+                break;
 #endif
 #ifdef EAFNOSUPPORT
-	    case EAFNOSUPPORT:
-		sym = @symbol(EAFNOSUPPORT);
-		typ = @symbol(unsupportedOperationSignal);
-		break;
+            case EAFNOSUPPORT:
+                sym = @symbol(EAFNOSUPPORT);
+                typ = @symbol(unsupportedOperationSignal);
+                break;
 #endif
 #ifdef EADDRINUSE
-	    case EADDRINUSE:
-		sym = @symbol(EADDRINUSE);
-		typ = @symbol(existingReferentSignal);
-		break;
+            case EADDRINUSE:
+                sym = @symbol(EADDRINUSE);
+                typ = @symbol(existingReferentSignal);
+                break;
 #endif
 #ifdef EADDRNOTAVAIL
-	    case EADDRNOTAVAIL:
-		sym = @symbol(EADDRNOTAVAIL);
-		typ = @symbol(noPermissionsSignal);
-		break;
+            case EADDRNOTAVAIL:
+                sym = @symbol(EADDRNOTAVAIL);
+                typ = @symbol(noPermissionsSignal);
+                break;
 #endif
 #ifdef ETIMEDOUT
-	    case ETIMEDOUT:
-		sym = @symbol(ETIMEDOUT);
-		typ = @symbol(peerFaultSignal);
-		break;
+            case ETIMEDOUT:
+                sym = @symbol(ETIMEDOUT);
+                typ = @symbol(peerFaultSignal);
+                break;
 #endif
 #ifdef ECONNREFUSED
-	    case ECONNREFUSED:
-		sym = @symbol(ECONNREFUSED);
-		typ = @symbol(peerFaultSignal);
-		break;
+            case ECONNREFUSED:
+                sym = @symbol(ECONNREFUSED);
+                typ = @symbol(peerFaultSignal);
+                break;
 #endif
 #ifdef ENETDOWN
-	    case ENETDOWN:
-		sym = @symbol(ENETDOWN);
-		typ = @symbol(peerFaultSignal);
-		break;
+            case ENETDOWN:
+                sym = @symbol(ENETDOWN);
+                typ = @symbol(peerFaultSignal);
+                break;
 #endif
 #ifdef ENETUNREACH
-	    case ENETUNREACH:
-		sym = @symbol(ENETUNREACH);
-		typ = @symbol(peerFaultSignal);
-		break;
+            case ENETUNREACH:
+                sym = @symbol(ENETUNREACH);
+                typ = @symbol(peerFaultSignal);
+                break;
 #endif
 #ifdef ENETRESET
-	    case ENETRESET:
-		sym = @symbol(ENETRESET);
-		typ = @symbol(peerFaultSignal);
-		break;
+            case ENETRESET:
+                sym = @symbol(ENETRESET);
+                typ = @symbol(peerFaultSignal);
+                break;
 #endif
 #ifdef ECONNABORTED
-	    case ECONNABORTED:
-		sym = @symbol(ECONNABORTED);
-		typ = @symbol(peerFaultSignal);
-		break;
+            case ECONNABORTED:
+                sym = @symbol(ECONNABORTED);
+                typ = @symbol(peerFaultSignal);
+                break;
 #endif
 #ifdef ECONNRESET
-	    case ECONNRESET:
-		sym = @symbol(ECONNRESET);
-		typ = @symbol(peerFaultSignal);
-		break;
+            case ECONNRESET:
+                sym = @symbol(ECONNRESET);
+                typ = @symbol(peerFaultSignal);
+                break;
 #endif
 #ifdef EISCONN
-	    case EISCONN:
-		sym = @symbol(EISCONN);
-		typ = @symbol(unpreparedOperationSignal);
-		break;
+            case EISCONN:
+                sym = @symbol(EISCONN);
+                typ = @symbol(unpreparedOperationSignal);
+                break;
 #endif
 #ifdef ENOTCONN
-	    case ENOTCONN:
-		sym = @symbol(ENOTCONN);
-		typ = @symbol(unpreparedOperationSignal);
-		break;
+            case ENOTCONN:
+                sym = @symbol(ENOTCONN);
+                typ = @symbol(unpreparedOperationSignal);
+                break;
 #endif
 #ifdef ESHUTDOWN
-	    case ESHUTDOWN:
-		sym = @symbol(ESHUTDOWN);
-		typ = @symbol(unpreparedOperationSignal);
-		break;
+            case ESHUTDOWN:
+                sym = @symbol(ESHUTDOWN);
+                typ = @symbol(unpreparedOperationSignal);
+                break;
 #endif
 #ifdef EHOSTDOWN
-	    case EHOSTDOWN:
-		sym = @symbol(EHOSTDOWN);
-		typ = @symbol(peerFaultSignal);
-		break;
+            case EHOSTDOWN:
+                sym = @symbol(EHOSTDOWN);
+                typ = @symbol(peerFaultSignal);
+                break;
 #endif
 #ifdef EHOSTUNREACH
-	    case EHOSTUNREACH:
-		sym = @symbol(EHOSTUNREACH);
-		typ = @symbol(peerFaultSignal);
-		break;
+            case EHOSTUNREACH:
+                sym = @symbol(EHOSTUNREACH);
+                typ = @symbol(peerFaultSignal);
+                break;
 #endif
 #ifdef EDQUOT
-	    case EDQUOT:
-		sym = @symbol(EDQUOT);
-		typ = @symbol(noResourcesSignal);
-		break;
+            case EDQUOT:
+                sym = @symbol(EDQUOT);
+                typ = @symbol(noResourcesSignal);
+                break;
 #endif
 
 #ifdef ENOMEDIUM
-	    case ENOMEDIUM:
-		sym = @symbol(ENOMEDIUM);
-		typ = @symbol(noResourcesSignal);
-		break;
+            case ENOMEDIUM:
+                sym = @symbol(ENOMEDIUM);
+                typ = @symbol(noResourcesSignal);
+                break;
 #endif
 #ifdef EMEDIUMTYPE
-	    case EMEDIUMTYPE:
-		sym = @symbol(EMEDIUMTYPE);
-		typ = @symbol(noResourcesSignal);
-		break;
-#endif
-
-	    default:
-		break;
-	}
+            case EMEDIUMTYPE:
+                sym = @symbol(EMEDIUMTYPE);
+                typ = @symbol(noResourcesSignal);
+                break;
+#endif
+
+            default:
+                break;
+        }
     }
 %}.
     holder := OSErrorHolder new.
     sym isNil ifTrue:[
-	sym := #ERROR_OTHER.
-	errNr notNil ifTrue:[
-	    "keep symbols as symbols"
-	    holder parameter:(errNr isString ifTrue:[errNr] ifFalse:[errNr asString]).
-	].
+        sym := #ERROR_OTHER.
+        errNr notNil ifTrue:[
+            "keep symbols as symbols"
+            holder parameter:(errNr isString ifTrue:[errNr] ifFalse:[errNr asString]).
+        ].
     ].
     holder errorSymbol:sym errorCategory:(typ ? #defaultOsErrorSignal).
     ^ holder
@@ -2602,238 +2603,238 @@
      */
 #ifdef EPERM
     if (sym == @symbol(EPERM)) {
-	RETURN ( __mkSmallInteger(EPERM) );
+        RETURN ( __mkSmallInteger(EPERM) );
     }
 #endif
 
 #ifdef ENOENT
     /* ERROR_FILE_NOT_FOUND is originally windows, but referd to in ExternalStream>>#openError: */
     if (sym == @symbol(ENOENT) || sym == @symbol(ERROR_FILE_NOT_FOUND)) {
-	RETURN ( __mkSmallInteger(ENOENT) );
+        RETURN ( __mkSmallInteger(ENOENT) );
     }
 #endif
 
 #ifdef ESRCH
     if (sym == @symbol(ESRCH)) {
-	RETURN ( __mkSmallInteger(ESRCH) );
+        RETURN ( __mkSmallInteger(ESRCH) );
     }
 #endif
 
 #ifdef EINTR
     if (sym == @symbol(EINTR)) {
-	RETURN ( __mkSmallInteger(EINTR) );
+        RETURN ( __mkSmallInteger(EINTR) );
     }
 #endif
 
 #ifdef EIO
     if (sym == @symbol(EIO)) {
-	RETURN ( __mkSmallInteger(EIO) );
+        RETURN ( __mkSmallInteger(EIO) );
     }
 #endif
 
 #ifdef ENXIO
     if (sym == @symbol(ENXIO)) {
-	RETURN ( __mkSmallInteger(ENXIO) );
+        RETURN ( __mkSmallInteger(ENXIO) );
     }
 #endif
 
 #ifdef E2BIG
     if (sym == @symbol(E2BIG)) {
-	RETURN ( __mkSmallInteger(E2BIG) );
+        RETURN ( __mkSmallInteger(E2BIG) );
     }
 #endif
 
 #ifdef ENOEXEC
     if (sym == @symbol(ENOEXEC)) {
-	RETURN ( __mkSmallInteger(ENOEXEC) );
+        RETURN ( __mkSmallInteger(ENOEXEC) );
     }
 #endif
 
 #ifdef ENOTSUP
 # if !defined(EOPNOTSUPP) || (ENOTSUP != EOPNOTSUPP)
     if (sym == @symbol(ENOTSUP)) {
-	RETURN ( __mkSmallInteger(ENOTSUP) );
+        RETURN ( __mkSmallInteger(ENOTSUP) );
     }
 # endif
 #endif
 
 #ifdef EBADF
     if (sym == @symbol(EBADF)) {
-	RETURN ( __mkSmallInteger(EBADF) );
+        RETURN ( __mkSmallInteger(EBADF) );
     }
 #endif
 
 #ifdef ECHILD
     if (sym == @symbol(ECHILD)) {
-	RETURN ( __mkSmallInteger(ECHILD) );
+        RETURN ( __mkSmallInteger(ECHILD) );
     }
 #endif
 
 #if defined(EAGAIN)
     if (sym == @symbol(EAGAIN)) {
-	RETURN ( __mkSmallInteger(EAGAIN) );
+        RETURN ( __mkSmallInteger(EAGAIN) );
     }
 #endif
 
 #ifdef ENOMEM
     if (sym == @symbol(ENOMEM)) {
-	RETURN ( __mkSmallInteger(ENOMEM) );
+        RETURN ( __mkSmallInteger(ENOMEM) );
     }
 #endif
 
 #ifdef EACCES
     if (sym == @symbol(EACCES)) {
-	RETURN ( __mkSmallInteger(EACCES) );
+        RETURN ( __mkSmallInteger(EACCES) );
     }
 #endif
 
 #ifdef EFAULT
     if (sym == @symbol(EFAULT)) {
-	RETURN ( __mkSmallInteger(EFAULT) );
+        RETURN ( __mkSmallInteger(EFAULT) );
     }
 #endif
 
 #ifdef EBUSY
     if (sym == @symbol(EBUSY)) {
-	RETURN ( __mkSmallInteger(EBUSY) );
+        RETURN ( __mkSmallInteger(EBUSY) );
     }
 #endif
 
 #ifdef EXDEV
     if (sym == @symbol(EXDEV)) {
-	RETURN ( __mkSmallInteger(EXDEV) );
+        RETURN ( __mkSmallInteger(EXDEV) );
     }
 #endif
 
 #ifdef ENODEV
     if (sym == @symbol(ENODEV)) {
-	RETURN ( __mkSmallInteger(ENODEV) );
+        RETURN ( __mkSmallInteger(ENODEV) );
     }
 #endif
 
 #ifdef ENOTDIR
     if (sym == @symbol(ENOTDIR)) {
-	RETURN ( __mkSmallInteger(ENOTDIR) );
+        RETURN ( __mkSmallInteger(ENOTDIR) );
     }
 #endif
 
 #ifdef EISDIR
     if (sym == @symbol(EISDIR)) {
-	RETURN ( __mkSmallInteger(EISDIR) );
+        RETURN ( __mkSmallInteger(EISDIR) );
     }
 #endif
 
 #ifdef EINVAL
     if (sym == @symbol(EINVAL)) {
-	RETURN ( __mkSmallInteger(EINVAL) );
+        RETURN ( __mkSmallInteger(EINVAL) );
     }
 #endif
 
 #ifdef ENFILE
     if (sym == @symbol(ENFILE)) {
-	RETURN ( __mkSmallInteger(ENFILE) );
+        RETURN ( __mkSmallInteger(ENFILE) );
     }
 #endif
 
 #ifdef EMFILE
     if (sym == @symbol(EMFILE)) {
-	RETURN ( __mkSmallInteger(EMFILE) );
+        RETURN ( __mkSmallInteger(EMFILE) );
     }
 #endif
 
 #ifdef ENOTTY
     if (sym == @symbol(ENOTTY)) {
-	RETURN ( __mkSmallInteger(ENOTTY) );
+        RETURN ( __mkSmallInteger(ENOTTY) );
     }
 #endif
 
 #ifdef EFBIG
     if (sym == @symbol(EFBIG)) {
-	RETURN ( __mkSmallInteger(EFBIG) );
+        RETURN ( __mkSmallInteger(EFBIG) );
     }
 #endif
 
 #ifdef ENOSPC
     if (sym == @symbol(ENOSPC)) {
-	RETURN ( __mkSmallInteger(ENOSPC) );
+        RETURN ( __mkSmallInteger(ENOSPC) );
     }
 #endif
 
 #ifdef ESPIPE
     if (sym == @symbol(ESPIPE)) {
-	RETURN ( __mkSmallInteger(ESPIPE) );
+        RETURN ( __mkSmallInteger(ESPIPE) );
     }
 #endif
 
 #ifdef EROFS
     if (sym == @symbol(EROFS)) {
-	RETURN ( __mkSmallInteger(EROFS) );
+        RETURN ( __mkSmallInteger(EROFS) );
     }
 #endif
 
 #ifdef EMLINK
     if (sym == @symbol(EMLINK)) {
-	RETURN ( __mkSmallInteger(EMLINK) );
+        RETURN ( __mkSmallInteger(EMLINK) );
     }
 #endif
 
 #ifdef EPIPE
     if (sym == @symbol(EPIPE)) {
-	RETURN ( __mkSmallInteger(EPIPE) );
+        RETURN ( __mkSmallInteger(EPIPE) );
     }
 #endif
 
 #ifdef EDOM
     if (sym == @symbol(EDOM)) {
-	RETURN ( __mkSmallInteger(EDOM) );
+        RETURN ( __mkSmallInteger(EDOM) );
     }
 #endif
 
 #ifdef ERANGE
     if (sym == @symbol(ERANGE)) {
-	RETURN ( __mkSmallInteger(ERANGE) );
+        RETURN ( __mkSmallInteger(ERANGE) );
     }
 #endif
 
 #ifdef EDEADLK
     if (sym == @symbol(EDEADLK)) {
-	RETURN ( __mkSmallInteger(EDEADLK) );
+        RETURN ( __mkSmallInteger(EDEADLK) );
     }
 #endif
 
 #ifdef ENAMETOOLONG
     if (sym == @symbol(ENAMETOOLONG)) {
-	RETURN ( __mkSmallInteger(ENAMETOOLONG) );
+        RETURN ( __mkSmallInteger(ENAMETOOLONG) );
     }
 #endif
 
 #ifdef ENOLCK
     if (sym == @symbol(ENOLCK)) {
-	RETURN ( __mkSmallInteger(ENOLCK) );
+        RETURN ( __mkSmallInteger(ENOLCK) );
     }
 #endif
 
 #ifdef ENOSYS
     if (sym == @symbol(ENOSYS)) {
-	RETURN ( __mkSmallInteger(ENOSYS) );
+        RETURN ( __mkSmallInteger(ENOSYS) );
     }
 #endif
 
 #ifdef ENOTEMPTY
     if (sym == @symbol(ENOTEMPTY)) {
-	RETURN ( __mkSmallInteger(ENOTEMPTY) );
+        RETURN ( __mkSmallInteger(ENOTEMPTY) );
     }
 #endif
 
 #ifdef EEXIST
     if (sym == @symbol(EEXIST)) {
-	RETURN ( __mkSmallInteger(EEXIST) );
+        RETURN ( __mkSmallInteger(EEXIST) );
     }
 #endif
 
 #ifdef EILSEQ
     if (sym == @symbol(EILSEQ)) {
-	RETURN ( __mkSmallInteger(EILSEQ) );
+        RETURN ( __mkSmallInteger(EILSEQ) );
     }
 #endif
 
@@ -2842,13 +2843,13 @@
      */
 #ifdef ENOTBLK
     if (sym == @symbol(ENOTBLK)) {
-	RETURN ( __mkSmallInteger(ENOTBLK) );
+        RETURN ( __mkSmallInteger(ENOTBLK) );
     }
 #endif
 
 #ifdef ETXTBSY
     if (sym == @symbol(ETXTBSY)) {
-	RETURN ( __mkSmallInteger(ETXTBSY) );
+        RETURN ( __mkSmallInteger(ETXTBSY) );
     }
 #endif
 
@@ -2857,25 +2858,25 @@
      */
 #ifdef EWOULDBLOCK
     if (sym == @symbol(EWOULDBLOCK)) {
-	RETURN ( __mkSmallInteger(EWOULDBLOCK) );
+        RETURN ( __mkSmallInteger(EWOULDBLOCK) );
     }
 #endif
 
 #ifdef EOVERFLOW
     if (sym == @symbol(EOVERFLOW)) {
-	RETURN ( __mkSmallInteger(EOVERFLOW) );
+        RETURN ( __mkSmallInteger(EOVERFLOW) );
     }
 #endif
 
 #ifdef ENOMSG
     if (sym == @symbol(ENOMSG)) {
-	RETURN ( __mkSmallInteger(ENOMSG) );
+        RETURN ( __mkSmallInteger(ENOMSG) );
     }
 #endif
 
 #ifdef ELOOP
     if (sym == @symbol(ELOOP)) {
-	RETURN ( __mkSmallInteger(ELOOP) );
+        RETURN ( __mkSmallInteger(ELOOP) );
     }
 #endif
 
@@ -2884,31 +2885,31 @@
      */
 #ifdef ETIME
     if (sym == @symbol(ETIME)) {
-	RETURN ( __mkSmallInteger(ETIME) );
+        RETURN ( __mkSmallInteger(ETIME) );
     }
 #endif
 
 #ifdef ENOSR
     if (sym == @symbol(ENOSR)) {
-	RETURN ( __mkSmallInteger(ENOSR) );
+        RETURN ( __mkSmallInteger(ENOSR) );
     }
 #endif
 
 #ifdef ENOSTR
     if (sym == @symbol(ENOSTR)) {
-	RETURN ( __mkSmallInteger(ENOSTR) );
+        RETURN ( __mkSmallInteger(ENOSTR) );
     }
 #endif
 
 #ifdef ECOMM
     if (sym == @symbol(ECOMM)) {
-	RETURN ( __mkSmallInteger(ECOMM) );
+        RETURN ( __mkSmallInteger(ECOMM) );
     }
 #endif
 
 #ifdef EPROTO
     if (sym == @symbol(EPROTO)) {
-	RETURN ( __mkSmallInteger(EPROTO) );
+        RETURN ( __mkSmallInteger(EPROTO) );
     }
 #endif
 
@@ -2917,13 +2918,13 @@
      */
 #ifdef ESTALE
     if (sym == @symbol(ESTALE)) {
-	RETURN ( __mkSmallInteger(ESTALE) );
+        RETURN ( __mkSmallInteger(ESTALE) );
     }
 #endif
 
 #ifdef EREMOTE
     if (sym == @symbol(EREMOTE)) {
-	RETURN ( __mkSmallInteger(EREMOTE) );
+        RETURN ( __mkSmallInteger(EREMOTE) );
     }
 #endif
 
@@ -2932,178 +2933,178 @@
      */
 #ifdef EINPROGRESS
     if (sym == @symbol(EINPROGRESS)) {
-	RETURN ( __mkSmallInteger(EINPROGRESS) );
+        RETURN ( __mkSmallInteger(EINPROGRESS) );
     }
 #endif
 
 #ifdef EALREADY
     if (sym == @symbol(EALREADY)) {
-	RETURN ( __mkSmallInteger(EALREADY) );
+        RETURN ( __mkSmallInteger(EALREADY) );
     }
 #endif
 
 #ifdef ENOTSOCK
     if (sym == @symbol(ENOTSOCK)) {
-	RETURN ( __mkSmallInteger(ENOTSOCK) );
+        RETURN ( __mkSmallInteger(ENOTSOCK) );
     }
 #endif
 
 #ifdef EDESTADDRREQ
     if (sym == @symbol(EDESTADDRREQ)) {
-	RETURN ( __mkSmallInteger(EDESTADDRREQ) );
+        RETURN ( __mkSmallInteger(EDESTADDRREQ) );
     }
 #endif
 
 #ifdef EMSGSIZE
     if (sym == @symbol(EMSGSIZE)) {
-	RETURN ( __mkSmallInteger(EMSGSIZE) );
+        RETURN ( __mkSmallInteger(EMSGSIZE) );
     }
 #endif
 
 #ifdef EPROTOTYPE
     if (sym == @symbol(EPROTOTYPE)) {
-	RETURN ( __mkSmallInteger(EPROTOTYPE) );
+        RETURN ( __mkSmallInteger(EPROTOTYPE) );
     }
 #endif
 
 #ifdef ENOPROTOOPT
     if (sym == @symbol(ENOPROTOOPT)) {
-	RETURN ( __mkSmallInteger(ENOPROTOOPT) );
+        RETURN ( __mkSmallInteger(ENOPROTOOPT) );
     }
 #endif
 
 #ifdef EPROTONOSUPPORT
     if (sym == @symbol(EPROTONOSUPPORT)) {
-	RETURN ( __mkSmallInteger(EPROTONOSUPPORT) );
+        RETURN ( __mkSmallInteger(EPROTONOSUPPORT) );
     }
 #endif
 
 #ifdef ESOCKTNOSUPPORT
     if (sym == @symbol(ESOCKTNOSUPPORT)) {
-	RETURN ( __mkSmallInteger(ESOCKTNOSUPPORT) );
+        RETURN ( __mkSmallInteger(ESOCKTNOSUPPORT) );
     }
 #endif
 
 #ifdef EOPNOTSUPP
     if (sym == @symbol(EOPNOTSUPP)) {
-	RETURN ( __mkSmallInteger(EOPNOTSUPP) );
+        RETURN ( __mkSmallInteger(EOPNOTSUPP) );
     }
 #endif
 
 #ifdef EPFNOSUPPORT
     if (sym == @symbol(EPFNOSUPPORT)) {
-	RETURN ( __mkSmallInteger(EPFNOSUPPORT) );
+        RETURN ( __mkSmallInteger(EPFNOSUPPORT) );
     }
 #endif
 
 #ifdef EAFNOSUPPORT
     if (sym == @symbol(EAFNOSUPPORT)) {
-	RETURN ( __mkSmallInteger(EAFNOSUPPORT) );
+        RETURN ( __mkSmallInteger(EAFNOSUPPORT) );
     }
 #endif
 
 #ifdef EADDRINUSE
     if (sym == @symbol(EADDRINUSE)) {
-	RETURN ( __mkSmallInteger(EADDRINUSE) );
+        RETURN ( __mkSmallInteger(EADDRINUSE) );
     }
 #endif
 
 #ifdef EADDRNOTAVAIL
     if (sym == @symbol(EADDRNOTAVAIL)) {
-	RETURN ( __mkSmallInteger(EADDRNOTAVAIL) );
+        RETURN ( __mkSmallInteger(EADDRNOTAVAIL) );
     }
 #endif
 
 #ifdef ETIMEDOUT
     if (sym == @symbol(ETIMEDOUT)) {
-	RETURN ( __mkSmallInteger(ETIMEDOUT) );
+        RETURN ( __mkSmallInteger(ETIMEDOUT) );
     }
 #endif
 
 #ifdef ECONNREFUSED
     if (sym == @symbol(ECONNREFUSED)) {
-	RETURN ( __mkSmallInteger(ECONNREFUSED) );
+        RETURN ( __mkSmallInteger(ECONNREFUSED) );
     }
 #endif
 
 #ifdef ENETDOWN
     if (sym == @symbol(ENETDOWN)) {
-	RETURN ( __mkSmallInteger(ENETDOWN) );
+        RETURN ( __mkSmallInteger(ENETDOWN) );
     }
 #endif
 
 #ifdef ENETUNREACH
     if (sym == @symbol(ENETUNREACH)) {
-	RETURN ( __mkSmallInteger(ENETUNREACH) );
+        RETURN ( __mkSmallInteger(ENETUNREACH) );
     }
 #endif
 
 #ifdef ENETRESET
     if (sym == @symbol(ENETRESET)) {
-	RETURN ( __mkSmallInteger(ENETRESET) );
+        RETURN ( __mkSmallInteger(ENETRESET) );
     }
 #endif
 
 #ifdef ECONNABORTED
     if (sym == @symbol(ECONNABORTED)) {
-	RETURN ( __mkSmallInteger(ECONNABORTED) );
+        RETURN ( __mkSmallInteger(ECONNABORTED) );
     }
 #endif
 
 #ifdef ECONNRESET
     if (sym == @symbol(ECONNRESET)) {
-	RETURN ( __mkSmallInteger(ECONNRESET) );
+        RETURN ( __mkSmallInteger(ECONNRESET) );
     }
 #endif
 
 #ifdef EISCONN
     if (sym == @symbol(EISCONN)) {
-	RETURN ( __mkSmallInteger(EISCONN) );
+        RETURN ( __mkSmallInteger(EISCONN) );
     }
 #endif
 
 #ifdef ENOTCONN
     if (sym == @symbol(ENOTCONN)) {
-	RETURN ( __mkSmallInteger(ENOTCONN) );
+        RETURN ( __mkSmallInteger(ENOTCONN) );
     }
 #endif
 
 #ifdef ESHUTDOWN
     if (sym == @symbol(ESHUTDOWN)) {
-	RETURN ( __mkSmallInteger(ESHUTDOWN) );
+        RETURN ( __mkSmallInteger(ESHUTDOWN) );
     }
 #endif
 
 #ifdef EHOSTDOWN
     if (sym == @symbol(EHOSTDOWN)) {
-	RETURN ( __mkSmallInteger(EHOSTDOWN) );
+        RETURN ( __mkSmallInteger(EHOSTDOWN) );
     }
 #endif
 
 #ifdef EHOSTUNREACH
     if (sym == @symbol(EHOSTUNREACH)) {
-	RETURN ( __mkSmallInteger(EHOSTUNREACH) );
+        RETURN ( __mkSmallInteger(EHOSTUNREACH) );
     }
 #endif
 
 #ifdef EREMOTEIO
     if (sym == @symbol(EREMOTEIO)) {
-	RETURN ( __mkSmallInteger(EREMOTEIO) );
+        RETURN ( __mkSmallInteger(EREMOTEIO) );
     }
 #endif
 #ifdef EDQUOT
     if (sym == @symbol(EDQUOT)) {
-	RETURN ( __mkSmallInteger(EDQUOT) );
+        RETURN ( __mkSmallInteger(EDQUOT) );
     }
 #endif
 #ifdef ENOMEDIUM
     if (sym == @symbol(ENOMEDIUM)) {
-	RETURN ( __mkSmallInteger(ENOMEDIUM) );
+        RETURN ( __mkSmallInteger(ENOMEDIUM) );
     }
 #endif
 #ifdef EMEDIUMTYPE
     if (sym == @symbol(EMEDIUMTYPE)) {
-	RETURN ( __mkSmallInteger(EMEDIUMTYPE) );
+        RETURN ( __mkSmallInteger(EMEDIUMTYPE) );
     }
 #endif
 
@@ -3124,29 +3125,29 @@
     "Internal lowLevel entry for combined fork & exec;
 
      If fork is false (chain a command):
-	 execute the OS command specified by the argument, aCommandPath, with
-	 arguments in argArray (no arguments, if nil).
-	 If successful, this method does not return and smalltalk is gone.
-	 If not successful, it does return.
-	 Normal use is with forkForCommand.
+         execute the OS command specified by the argument, aCommandPath, with
+         arguments in argArray (no arguments, if nil).
+         If successful, this method does not return and smalltalk is gone.
+         If not successful, it does return.
+         Normal use is with forkForCommand.
 
      If fork is true (subprocess command execution):
-	fork a child to do the above.
-	The process id of the child process is returned; nil if the fork failed.
+        fork a child to do the above.
+        The process id of the child process is returned; nil if the fork failed.
 
      fdColl contains the filedescriptors, to be used for the child (if fork is true).
-	fdArray[1] = 15 -> use fd 15 as stdin.
-	If an element of the array is set to nil, the corresponding filedescriptor
-	will be closed for the child.
-	fdArray[1] == StdIn for child
-	fdArray[2] == StdOut for child
-	fdArray[3] == StdErr for child
-	on VMS, these must be channels as returned by createMailBox.
-	All filedescriptors not present in fdColl will be closed for the child.
+        fdArray[1] = 15 -> use fd 15 as stdin.
+        If an element of the array is set to nil, the corresponding filedescriptor
+        will be closed for the child.
+        fdArray[1] == StdIn for child
+        fdArray[2] == StdOut for child
+        fdArray[3] == StdErr for child
+        on VMS, these must be channels as returned by createMailBox.
+        All filedescriptors not present in fdColl will be closed for the child.
 
      If newPgrp is true, the subprocess will be established in a new process group.
-	The processgroup will be equal to id.
-	newPgrp is not used on WIN32 and VMS systems.
+        The processgroup will be equal to id.
+        newPgrp is not used on WIN32 and VMS systems.
 
      environmentDictionary specifies environment variables which are passed differently from
      the current environment. If non-nil, it must be a dictionary providing
@@ -3154,33 +3155,33 @@
      To pass a variable as empty (i.e. unset), pass a nil value.
 
      Notice: this used to be two separate ST-methods; however, in order to use
-	    vfork on some machines, it had to be merged into one, to avoid write
-	    accesses to ST/X memory from the vforked-child.
-	    The code below only does read accesses."
+            vfork on some machines, it had to be merged into one, to avoid write
+            accesses to ST/X memory from the vforked-child.
+            The code below only does read accesses."
 
     |envArray argArray fdArray dirName cnt aCommandPath|
 
     environmentDictionary notEmptyOrNil ifTrue:[
-	envArray := Array new:environmentDictionary size.
-	cnt := 1.
-	environmentDictionary keysAndValuesDo:[:key :val |
-	    val isNil ifTrue:[
-		envArray at:cnt put:((self encodePath:key), '=')
-	    ] ifFalse:[
-		envArray at:cnt put:((self encodePath:key), '=', (self encodePath:val))
-	    ].
-	    cnt := cnt + 1.
-	].
+        envArray := Array new:environmentDictionary size.
+        cnt := 1.
+        environmentDictionary keysAndValuesDo:[:key :val |
+            val isNil ifTrue:[
+                envArray at:cnt put:((self encodePath:key), '=')
+            ] ifFalse:[
+                envArray at:cnt put:((self encodePath:key), '=', (self encodePath:val))
+            ].
+            cnt := cnt + 1.
+        ].
     ].
     argColl notNil ifTrue:[
-	argArray := argColl asArray collect:[:eachArg| self encodePath:eachArg].
+        argArray := argColl asArray collect:[:eachArg| self encodePath:eachArg].
     ].
     fdColl notNil ifTrue:[
-	fdArray := fdColl asArray
+        fdArray := fdColl asArray
     ].
     aDirectory notNil ifTrue:[
-	dirName := aDirectory asFilename osNameForFile.
-	dirName := self encodePath:dirName.
+        dirName := aDirectory asFilename osNameForFile.
+        dirName := self encodePath:dirName.
     ].
     aCommandPath := self encodePath:aCommandPathArg.
 
@@ -3196,210 +3197,210 @@
     char **_env, **_nEnv;
 
     if (__isStringLike(aCommandPath) &&
-	((argArray == nil) || __isArrayLike(argArray)) &&
-	((fdArray == nil) || __isArrayLike(fdArray))
+        ((argArray == nil) || __isArrayLike(argArray)) &&
+        ((fdArray == nil) || __isArrayLike(fdArray))
     ) {
-	nargs = argArray == nil ? 0 : __arraySize(argArray);
-	argv = (char **) malloc(sizeof(char *) * (nargs + 1));
-	if (argv) {
-	    int nOldEnv, nNewEnv;
-
-	    for (i=0; i < nargs; i++) {
-		arg = __ArrayInstPtr(argArray)->a_element[i];
-		if (__isStringLike(arg)) {
-		    argv[i] = (char *) __stringVal(arg);
-		} else {
-		    argv[i] = "";
-		}
-	    }
-	    argv[i] = NULL;
-
-	    /*
-	     * number of new items in environment ..
-	     */
-	    nNewEnv = 0;
-	    if ((envArray != nil) && __isArrayLike(envArray)) {
-		nNewEnv = __arraySize(envArray);
-	    }
-
-	    if (nNewEnv == 0) {
-		_nEnv = environ;
-	    } else {
-		_env = environ;
-		/*
-		 * get size of environment
-		 */
-		nOldEnv = 0;
-		if (_env) {
-		    while (*_env) {
-			nOldEnv++;
-			_env++;
-		    }
-		}
-
-		/*
-		 * generate a new environment
-		 * I have not found a spec which defines if
-		 * items at the end overwrite previous definitions,
-		 * or if the first encountered definition is valid.
-		 * To be prepared for any case, simply add the new definitions
-		 * at both ends - that should do it in any case.
-		 * Someone with more know-how may want to fix this.
-		 * getenv() searches for the first entry.
-		 * But maybe someone creates a Dictionary from the environment.
-		 * In this case the last entry would overwrite previous entries.
-		 */
-		_nEnv = (char **)malloc(sizeof(char *) * (nNewEnv + nOldEnv + nNewEnv + 1));
-		if (_nEnv) {
-		    char **eO, **eN;
-
-		    eN = _nEnv;
-		    if (nNewEnv) {
-			/*
-			 * add new items at the front ...
-			 */
-			int i;
-			OBJ *t;
-
-			for (i=0, t = __arrayVal(envArray);
-			     i < __arraySize(envArray);
-			     i++, t++) {
-
-			    if (__isStringLike(*t)) {
-				*eN++ = (char *)__stringVal(*t);
-			    }
-			}
-		    }
-
-		    if (nOldEnv) {
-			/*
-			 * append old environment
-			 */
-			for (eO = environ; *eO; *eN++ = *eO++)
-			    continue;
-		    }
-
-		    if (nNewEnv) {
-			/*
-			 * append new items again at the end
-			 */
-			for (eO = _nEnv, i=0; i<nNewEnv; i++) {
-			    *eN++ = *eO++;
-			}
-		    }
-		    *eN = NULL;
-		}
-	    }
-
-	    if (doFork == true) {
-		/*
-		 * fork a subprocess.
-		 */
-		int nfd;
-
-		nfd = fdArray == nil ? 0 : __arraySize(fdArray);
-		id = FORK ();
-		if (id == 0) {
-		    /*
-		    ** In child.
-		    ** first: dup filedescriptors.
-		    */
-		    for (i = 0; i < nfd; i++) {
-			OBJ fd;
-			int rslt;
-
-			fd = __arrayVal(fdArray)[i];
-			if (__isSmallInteger(fd) && (__intVal(fd) != i)) {
-			    do {
-				rslt = dup2(__intVal(fd), i);
-			    } while ((rslt < 0) && (errno == EINTR));
-			}
-		    }
-		    /*
-		    ** Second: close descriptors
-		    **         marked as unwanted
-		    ** (extra loop to allow duping of low filedescriptor numbers to
-		    **  higher fd numbers)
-		    */
-		    for (i = 0; i < nfd; i++) {
-			if (__arrayVal(fdArray)[i] == nil) {
-			    close(i);
-			}
-		    }
-
-		    /*
-		    ** third: close all filedescriptors larger
-		    ** then the explicitely closed or duped
-		    ** filedescriptors
-		    */
+        nargs = argArray == nil ? 0 : __arraySize(argArray);
+        argv = (char **) malloc(sizeof(char *) * (nargs + 1));
+        if (argv) {
+            int nOldEnv, nNewEnv;
+
+            for (i=0; i < nargs; i++) {
+                arg = __ArrayInstPtr(argArray)->a_element[i];
+                if (__isStringLike(arg)) {
+                    argv[i] = (char *) __stringVal(arg);
+                } else {
+                    argv[i] = "";
+                }
+            }
+            argv[i] = NULL;
+
+            /*
+             * number of new items in environment ..
+             */
+            nNewEnv = 0;
+            if ((envArray != nil) && __isArrayLike(envArray)) {
+                nNewEnv = __arraySize(envArray);
+            }
+
+            if (nNewEnv == 0) {
+                _nEnv = environ;
+            } else {
+                _env = environ;
+                /*
+                 * get size of environment
+                 */
+                nOldEnv = 0;
+                if (_env) {
+                    while (*_env) {
+                        nOldEnv++;
+                        _env++;
+                    }
+                }
+
+                /*
+                 * generate a new environment
+                 * I have not found a spec which defines if
+                 * items at the end overwrite previous definitions,
+                 * or if the first encountered definition is valid.
+                 * To be prepared for any case, simply add the new definitions
+                 * at both ends - that should do it in any case.
+                 * Someone with more know-how may want to fix this.
+                 * getenv() searches for the first entry.
+                 * But maybe someone creates a Dictionary from the environment.
+                 * In this case the last entry would overwrite previous entries.
+                 */
+                _nEnv = (char **)malloc(sizeof(char *) * (nNewEnv + nOldEnv + nNewEnv + 1));
+                if (_nEnv) {
+                    char **eO, **eN;
+
+                    eN = _nEnv;
+                    if (nNewEnv) {
+                        /*
+                         * add new items at the front ...
+                         */
+                        int i;
+                        OBJ *t;
+
+                        for (i=0, t = __arrayVal(envArray);
+                             i < __arraySize(envArray);
+                             i++, t++) {
+
+                            if (__isStringLike(*t)) {
+                                *eN++ = (char *)__stringVal(*t);
+                            }
+                        }
+                    }
+
+                    if (nOldEnv) {
+                        /*
+                         * append old environment
+                         */
+                        for (eO = environ; *eO; *eN++ = *eO++)
+                            continue;
+                    }
+
+                    if (nNewEnv) {
+                        /*
+                         * append new items again at the end
+                         */
+                        for (eO = _nEnv, i=0; i<nNewEnv; i++) {
+                            *eN++ = *eO++;
+                        }
+                    }
+                    *eN = NULL;
+                }
+            }
+
+            if (doFork == true) {
+                /*
+                 * fork a subprocess.
+                 */
+                int nfd;
+
+                nfd = fdArray == nil ? 0 : __arraySize(fdArray);
+                id = FORK ();
+                if (id == 0) {
+                    /*
+                    ** In child.
+                    ** first: dup filedescriptors.
+                    */
+                    for (i = 0; i < nfd; i++) {
+                        OBJ fd;
+                        int rslt;
+
+                        fd = __arrayVal(fdArray)[i];
+                        if (__isSmallInteger(fd) && (__intVal(fd) != i)) {
+                            do {
+                                rslt = dup2(__intVal(fd), i);
+                            } while ((rslt < 0) && (errno == EINTR));
+                        }
+                    }
+                    /*
+                    ** Second: close descriptors
+                    **         marked as unwanted
+                    ** (extra loop to allow duping of low filedescriptor numbers to
+                    **  higher fd numbers)
+                    */
+                    for (i = 0; i < nfd; i++) {
+                        if (__arrayVal(fdArray)[i] == nil) {
+                            close(i);
+                        }
+                    }
+
+                    /*
+                    ** third: close all filedescriptors larger
+                    ** then the explicitely closed or duped
+                    ** filedescriptors
+                    */
 #ifndef OPEN_MAX
 # define OPEN_MAX       256
 #endif
-		    for ( ;i < OPEN_MAX; i++) {
-			close(i);
-		    }
-
-		    if (newPgrp == true) {
+                    for ( ;i < OPEN_MAX; i++) {
+                        close(i);
+                    }
+
+                    if (newPgrp == true) {
 #ifndef NEXT
-			setsid();
+                        setsid();
 #endif
 #if defined(TIOCSCTTY)
-			ioctl(0, TIOCSCTTY, 0) ;
+                        ioctl(0, TIOCSCTTY, 0) ;
 #endif
 
 #if defined(TIOCSPGRP)
-			{
-			    int pgrp = getpid();
-
-			    ioctl(0, TIOCSPGRP, (char *)&pgrp);
-			}
+                        {
+                            int pgrp = getpid();
+
+                            ioctl(0, TIOCSPGRP, (char *)&pgrp);
+                        }
 #endif
 #if defined(_POSIX_JOB_CONTROL)
-			(void) setpgid(0, 0);
+                        (void) setpgid(0, 0);
 #else
 # if defined(BSD) || defined(LINUX)
-			(void) setpgrp(0);
-# endif
-#endif
-		    }
-
-		    if (dirName == nil || chdir((char *)__stringVal(dirName)) == 0) {
-			execve((char *)__stringVal(aCommandPath), argv, _nEnv);
-		    }
-		    /* reached if chdir failed or aCommandPathh cannot be executed */
-		    _exit(127);                 /* POSIX 2 compatible exit value */
-		}
-	    } else {
-		/*
-		 * no subprocess (i.e. transfer to another program)
-		 */
-		if (dirName == nil || chdir((char *)__stringVal(dirName)) == 0) {
-		    execve((char *)__stringVal(aCommandPath), argv, _nEnv);
-		}
-		/*
-		 * reached if chdir failed or command-path cannot be executed
-		 */
-		id = -1;
-	    }
-
-	    if (nNewEnv && (_nEnv != NULL)) {
-		/*
-		 * free new environment stuff
-		 */
-		free(_nEnv);
-	    }
-
-	    free(argv);
-
-	    /*
-	     * In parent: succes or failure
-	     */
-	    if (id == -1) {
-		RETURN (nil);
-	    } else {
-		RETURN (__mkSmallInteger(id));
-	    }
-	}
+                        (void) setpgrp(0);
+# endif
+#endif
+                    }
+
+                    if (dirName == nil || chdir((char *)__stringVal(dirName)) == 0) {
+                        execve((char *)__stringVal(aCommandPath), argv, _nEnv);
+                    }
+                    /* reached if chdir failed or aCommandPathh cannot be executed */
+                    _exit(127);                 /* POSIX 2 compatible exit value */
+                }
+            } else {
+                /*
+                 * no subprocess (i.e. transfer to another program)
+                 */
+                if (dirName == nil || chdir((char *)__stringVal(dirName)) == 0) {
+                    execve((char *)__stringVal(aCommandPath), argv, _nEnv);
+                }
+                /*
+                 * reached if chdir failed or command-path cannot be executed
+                 */
+                id = -1;
+            }
+
+            if (nNewEnv && (_nEnv != NULL)) {
+                /*
+                 * free new environment stuff
+                 */
+                free(_nEnv);
+            }
+
+            free(argv);
+
+            /*
+             * In parent: succes or failure
+             */
+            if (id == -1) {
+                RETURN (nil);
+            } else {
+                RETURN (__mkSmallInteger(id));
+            }
+        }
     }
 %}.
     "
@@ -3415,9 +3416,9 @@
 
      id := OperatingSystem fork.
      id == 0 ifTrue:[
-	'I am the child'.
-	OperatingSystem exec:'/bin/ls' withArguments:#('ls' '/tmp').
-	'not reached'.
+        'I am the child'.
+        OperatingSystem exec:'/bin/ls' withArguments:#('ls' '/tmp').
+        'not reached'.
      ]
     "
     "
@@ -3425,11 +3426,11 @@
 
      id := OperatingSystem fork.
      id == 0 ifTrue:[
-	'I am the child'.
-	OperatingSystem
-	   exec:'/bin/sh'
-	   withArguments:#('sh' '-c' 'sleep 2;echo 1;sleep 2;echo 2').
-	'not reached'.
+        'I am the child'.
+        OperatingSystem
+           exec:'/bin/sh'
+           withArguments:#('sh' '-c' 'sleep 2;echo 1;sleep 2;echo 2').
+        'not reached'.
      ].
      id printNL.
      (Delay forSeconds:3.5) wait.
@@ -3466,8 +3467,8 @@
 
      id := OperatingSystem fork.
      id == 0 ifTrue:[
-	'I am the child process' printCR.
-	OperatingSystem exit
+        'I am the child process' printCR.
+        OperatingSystem exit
      ]
     "
 !
@@ -3493,36 +3494,36 @@
     aCommandString isNil ifTrue:[^ nil].
 
     (in := anExternalInStream) isNil ifTrue:[
-	nullStream := Filename nullDevice readWriteStream.
-	in := nullStream.
+        nullStream := Filename nullDevice readWriteStream.
+        in := nullStream.
     ].
     (out := anExternalOutStream) isNil ifTrue:[
-	nullStream isNil ifTrue:[nullStream := Filename nullDevice writeStream].
-	out := nullStream.
+        nullStream isNil ifTrue:[nullStream := Filename nullDevice writeStream].
+        out := nullStream.
     ].
     (err := anExternalErrStream) isNil ifTrue:[
-	err := out
+        err := out
     ].
     anAuxiliaryStream notNil ifTrue:[
-	auxFd := anAuxiliaryStream fileDescriptor
+        auxFd := anAuxiliaryStream fileDescriptor
     ].
 
     shellAndArgs := self commandAndArgsForOSCommand:aCommandString.
 
     rslt := self
-	exec:(shellAndArgs at:1)
-	withArguments:(shellAndArgs at:2)
-	environment:anEvironmentDictionary
-	fileDescriptors:(Array with:in fileDescriptor
-			       with:out fileDescriptor
-			       with:err fileDescriptor
-			       with:auxFd)
-	fork:true
-	newPgrp:true "/ false
-	inDirectory:dir.
+        exec:(shellAndArgs at:1)
+        withArguments:(shellAndArgs at:2)
+        environment:anEvironmentDictionary
+        fileDescriptors:(Array with:in fileDescriptor
+                               with:out fileDescriptor
+                               with:err fileDescriptor
+                               with:auxFd)
+        fork:true
+        newPgrp:true "/ false
+        inDirectory:dir.
 
     nullStream notNil ifTrue:[
-	nullStream close.
+        nullStream close.
     ].
 
     ^ rslt
@@ -3547,7 +3548,7 @@
      The following will no longer work. monitorPid has disappeared
 
      pid notNil ifTrue:[
-	 Processor monitorPid:pid action:[:OSstatus | sema signal ].
+         Processor monitorPid:pid action:[:OSstatus | sema signal ].
      ].
      in close.
      out close.
@@ -3572,8 +3573,8 @@
      and the other elements are the arguments to the command. No shell is invoked in this case."
 
     aCommandStringOrArray isNonByteCollection ifTrue:[
-	"if an array is passed, the command string has already been parsed an no shell is invoked"
-	^ Array with:aCommandStringOrArray first with:aCommandStringOrArray.
+        "if an array is passed, the command string has already been parsed an no shell is invoked"
+        ^ Array with:aCommandStringOrArray first with:aCommandStringOrArray.
     ].
 
     "/
@@ -3597,10 +3598,10 @@
      Here we get an absolute path to the running executable."
     info := '/proc/self/exe' asFilename linkInfo.
     info notNil ifTrue:[
-	path := info path.
-	path notEmptyOrNil ifTrue:[
-	    ^ path
-	].
+        path := info path.
+        path notEmptyOrNil ifTrue:[
+            ^ path
+        ].
      ].
 
     "Fall back - do it the hard way"
@@ -3621,35 +3622,35 @@
 
     commandFilename := aCommand asFilename.
     commandFilename isAbsolute ifTrue:[
-	^ commandFilename pathName
+        ^ commandFilename pathName
     ].
     commandFilename isExplicitRelative ifTrue:[
-	 ^ commandFilename pathName
+         ^ commandFilename pathName
     ].
     (aCommand includes:$/) ifTrue:[
-	"/ something like "smalltalk/stx", if executed from a parent directory
-	^ ('./',aCommand) asFilename pathName
+        "/ something like "smalltalk/stx", if executed from a parent directory
+        ^ ('./',aCommand) asFilename pathName
     ].
 
     path := self getEnvironment:'PATH'.
     path notEmptyOrNil ifTrue:[
-	(path asCollectionOfSubstringsSeparatedBy:self pathSeparator) do:[:eachPathComponent |
-	    eachPathComponent isEmpty ifTrue:[
-		f := commandFilename
-	    ] ifFalse:[
-		f := eachPathComponent asFilename construct:aCommand.
-	    ].
-	    self executableFileExtensions do:[:eachExtension |
-		eachExtension notEmpty ifTrue:[
-		    fExt := f addSuffix:eachExtension.
-		] ifFalse:[
-		    fExt := f.
-		].
-		fExt isExecutable ifTrue:[
-		    ^ fExt pathName
-		].
-	    ].
-	].
+        (path asCollectionOfSubstringsSeparatedBy:self pathSeparator) do:[:eachPathComponent |
+            eachPathComponent isEmpty ifTrue:[
+                f := commandFilename
+            ] ifFalse:[
+                f := eachPathComponent asFilename construct:aCommand.
+            ].
+            self executableFileExtensions do:[:eachExtension |
+                eachExtension notEmpty ifTrue:[
+                    fExt := f addSuffix:eachExtension.
+                ] ifFalse:[
+                    fExt := f.
+                ].
+                fExt isExecutable ifTrue:[
+                    ^ fExt pathName
+                ].
+            ].
+        ].
     ].
     ^ nil
 
@@ -3676,11 +3677,11 @@
 
 %{
      if (__isSmallInteger(anInteger)) {
-	if (@global(ExternalStream:FileOpenTrace) == true) {
-	    fprintf(stderr, "close [UnixOp] fd=%d\n", (int)__intVal(anInteger));
-	}
-	close(__intVal(anInteger));
-	RETURN(self);
+        if (@global(ExternalStream:FileOpenTrace) == true) {
+            fprintf(stderr, "close [UnixOp] fd=%d\n", (int)__intVal(anInteger));
+        }
+        close(__intVal(anInteger));
+        RETURN(self);
      }
 %}.
      ^ self primitiveFailed.
@@ -3699,13 +3700,13 @@
       && __isSmallInteger(outFd)
       && __isSmallInteger(startIdx)
       && __isSmallInteger(count)) {
-	int nWritten;
-
-	nWritten = sendfile(__intVal(outFd), __intVal(inFd), __intVal(startIdx), __intVal(count));
-	if (nWritten < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	}
-	RETURN (__mkSmallInteger(nWritten));
+        int nWritten;
+
+        nWritten = sendfile(__intVal(outFd), __intVal(inFd), __intVal(startIdx), __intVal(count));
+        if (nWritten < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+        }
+        RETURN (__mkSmallInteger(nWritten));
      }
 #endif
 %}.
@@ -3740,10 +3741,10 @@
 
 %{
     if (__isStringLike(encodedPathName) && __isSmallInteger(umask)) {
-	if (mkdir(__stringVal(encodedPathName), __smallIntegerVal(umask)) >= 0) {
-	    RETURN(true);
-	}
-	@global(LastErrorNumber) = __mkSmallInteger(errno);
+        if (mkdir(__stringVal(encodedPathName), __smallIntegerVal(umask)) >= 0) {
+            RETURN(true);
+        }
+        @global(LastErrorNumber) = __mkSmallInteger(errno);
     }
 %}.
     "/ could not create - if it already existed this is ok
@@ -3785,16 +3786,16 @@
     int ret;
 
     if (__isStringLike(encodedOldPathName) && __isStringLike(encodedNewPathName)) {
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = link((char *) __stringVal(encodedOldPathName), (char *) __stringVal(encodedNewPathName));
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( false );
-	}
-	RETURN (true);
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = link((char *) __stringVal(encodedOldPathName), (char *) __stringVal(encodedNewPathName));
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( false );
+        }
+        RETURN (true);
     }
 %}.
     "/
@@ -3821,26 +3822,26 @@
     int ret;
 
     if (__isStringLike(encodedOldPathName) && __isStringLike(encodedNewPathName)) {
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = symlink((char *) __stringVal(encodedOldPathName), (char *) __stringVal(encodedNewPathName));
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
-	if (ret >= 0) {
-	    RETURN (true);
-	}
-	@global(LastErrorNumber) = error = __mkSmallInteger(errno);
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = symlink((char *) __stringVal(encodedOldPathName), (char *) __stringVal(encodedNewPathName));
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
+        if (ret >= 0) {
+            RETURN (true);
+        }
+        @global(LastErrorNumber) = error = __mkSmallInteger(errno);
     }
 #endif
 %}.
     (encodedOldPathName isString not or:[encodedNewPathName isString not]) ifTrue:[
-	"/
-	"/ bad argument(s) given
-	"/
-	^ self primitiveFailed
+        "/
+        "/ bad argument(s) given
+        "/
+        ^ self primitiveFailed
     ].
     error notNil ifTrue:[
-	(self errorHolderForNumber:error) reportError
+        (self errorHolderForNumber:error) reportError
     ].
 
     "/
@@ -3858,13 +3859,13 @@
     "open a file, return an os specific fileHandle.
      openmode is a symbol defining the way to open
      valid modes are:
-	#O_RDONLY
-	#O_RDWR
-	#O_WRONLY
-	#O_CREAT
-	#O_APPEND
-	#O_SYNC
-	#O_LARGEFILE
+        #O_RDONLY
+        #O_RDWR
+        #O_WRONLY
+        #O_CREAT
+        #O_APPEND
+        #O_SYNC
+        #O_LARGEFILE
 
      This is a private entry, but maybe useful to open/create a file in a special mode,
      which is proprietrary to the operatingSystem."
@@ -3881,55 +3882,55 @@
     int n;
 
     if (!__isStringLike(encodedPathName)) {
-	error = @symbol(badArgument1);
-	goto err;
+        error = @symbol(badArgument1);
+        goto err;
     }
     if (!__isArrayLike(attributes)) {
-	error = @symbol(badArgument2);
-	goto err;
+        error = @symbol(badArgument2);
+        goto err;
     }
     if (modeInteger == nil) {
-	mode = 0644;
+        mode = 0644;
     } else if (__isSmallInteger(modeInteger)) {
-	mode = __intVal(modeInteger);
+        mode = __intVal(modeInteger);
     } else {
-	error = @symbol(badArgument3);
-	goto err;
+        error = @symbol(badArgument3);
+        goto err;
     }
 
     nAttributes = __arraySize(attributes);
     for (n = 0, ap = __arrayVal(attributes); n < nAttributes; n++) {
-	OBJ attribute = ap[n];
-
-	if (attribute == @symbol(O_RDONLY)) {
-	    openFlags |= O_RDONLY;
-	} else if (attribute == @symbol(O_RDWR)) {
-	    openFlags |= O_RDWR;
-	} else if (attribute == @symbol(O_WRONLY)) {
-	    openFlags |= O_WRONLY;
-	} else if (attribute == @symbol(O_CREAT)) {
-	    openFlags |= O_CREAT;
-	} else if (attribute == @symbol(O_APPEND)) {
-	    openFlags |= O_APPEND;
-	} else if (attribute == @symbol(O_EXCL)) {
-	    openFlags |= O_EXCL;
-	} else if (attribute == @symbol(O_TRUNC)) {
-	    openFlags |= O_TRUNC;
-	} else if (attribute == @symbol(O_LARGEFILE)) {
+        OBJ attribute = ap[n];
+
+        if (attribute == @symbol(O_RDONLY)) {
+            openFlags |= O_RDONLY;
+        } else if (attribute == @symbol(O_RDWR)) {
+            openFlags |= O_RDWR;
+        } else if (attribute == @symbol(O_WRONLY)) {
+            openFlags |= O_WRONLY;
+        } else if (attribute == @symbol(O_CREAT)) {
+            openFlags |= O_CREAT;
+        } else if (attribute == @symbol(O_APPEND)) {
+            openFlags |= O_APPEND;
+        } else if (attribute == @symbol(O_EXCL)) {
+            openFlags |= O_EXCL;
+        } else if (attribute == @symbol(O_TRUNC)) {
+            openFlags |= O_TRUNC;
+        } else if (attribute == @symbol(O_LARGEFILE)) {
 #ifdef O_LARGEFILE
-	    openFlags |= O_LARGEFILE;
+            openFlags |= O_LARGEFILE;
 #else
-	    error = @symbol(badArgument2);
-	    goto err;
-#endif
-	} else if (attribute == @symbol(O_SYNC)) {
+            error = @symbol(badArgument2);
+            goto err;
+#endif
+        } else if (attribute == @symbol(O_SYNC)) {
 #ifdef O_SYNC
-	    openFlags |= O_SYNC;
+            openFlags |= O_SYNC;
 #else
-	    error = @symbol(badArgument2);
-	    goto err;
-#endif
-	}
+            error = @symbol(badArgument2);
+            goto err;
+#endif
+        }
     }
 
 #if defined(O_NONBLOCK)
@@ -3941,29 +3942,29 @@
 again:
     fd = open((char *) __stringVal(encodedPathName), openFlags, mode);
     if (fd < 0) {
-	if (errno == EINTR) {
-	    __HANDLE_INTERRUPTS__;
-	    goto again;
-	} else {
-	    error = __mkSmallInteger(errno);
-	    goto err;
-	}
+        if (errno == EINTR) {
+            __HANDLE_INTERRUPTS__;
+            goto again;
+        } else {
+            error = __mkSmallInteger(errno);
+            goto err;
+        }
     }
     fileDescriptor = __mkSmallInteger(fd);
 err:;
 %}.
     ^ fileDescriptor notNil ifTrue:[
-	FileDescriptorHandle for:fileDescriptor.
+        FileDescriptorHandle for:fileDescriptor.
     ] ifFalse:[
-	(self errorHolderForNumber:error) reportError
-    ].
-
-    "
-	self open:'/etc/hosts' attributes:#(O_RDONLY) mode:nil
-	self open:'/tmp/xxzz' attributes:#(O_RDWR O_CREAT) mode:8r611
-	self open:'/etc/passwd' attributes:#(O_RDWR) mode:nil
-	self open:'/no one knows this file' attributes:#(O_RDONLY) mode:nil
-	self open:'foo/bar/baz' attributes:#(O_RDWR O_CREAT) mode:nil
+        (self errorHolderForNumber:error) reportError
+    ].
+
+    "
+        self open:'/etc/hosts' attributes:#(O_RDONLY) mode:nil
+        self open:'/tmp/xxzz' attributes:#(O_RDWR O_CREAT) mode:8r611
+        self open:'/etc/passwd' attributes:#(O_RDWR) mode:nil
+        self open:'/no one knows this file' attributes:#(O_RDONLY) mode:nil
+        self open:'foo/bar/baz' attributes:#(O_RDWR O_CREAT) mode:nil
     "
 !
 
@@ -3999,8 +4000,8 @@
     ^ self executeCommand:(Array with:'/bin/cp' with:'-af' with:sourcePathName with:destination)
 
     "
-	self recursiveCopyDirectory:'packages' to:'foo'.
-	self recursiveRemoveDirectory:'foo'.
+        self recursiveCopyDirectory:'packages' to:'foo'.
+        self recursiveRemoveDirectory:'foo'.
     "
 
     "Modified: / 5.6.1998 / 18:33:57 / cg"
@@ -4033,16 +4034,16 @@
     int ret;
 
     if (__isStringLike(encodedPathName)) {
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = rmdir((char *) __stringVal(encodedPathName));
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( false );
-	}
-	RETURN (true);
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = rmdir((char *) __stringVal(encodedPathName));
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( false );
+        }
+        RETURN (true);
     }
 %}.
     "/
@@ -4068,16 +4069,16 @@
     int ret;
 
     if (__isStringLike(encodedPathName)) {
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = unlink((char *) __stringVal(encodedPathName));
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( false );
-	}
-	RETURN (true);
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = unlink((char *) __stringVal(encodedPathName));
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( false );
+        }
+        RETURN (true);
     }
 %}.
     ^ self primitiveFailed
@@ -4100,27 +4101,27 @@
 
     if (__isStringLike(encodedOldPathName) && __isStringLike(encodedNewPathName)) {
 #if defined(HAS_RENAME)
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = rename((char *) __stringVal(encodedOldPathName), (char *) __stringVal(encodedNewPathName));
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = rename((char *) __stringVal(encodedOldPathName), (char *) __stringVal(encodedNewPathName));
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
 #else
-	ret = link((char *) __stringVal(encodedOldPathName), (char *) __stringVal(encodedNewPathName));
-	if (ret >= 0) {
-	    ret = unlink((char *) __stringVal(encodedOldPathName));
-	    if (ret < 0) {
-		eno = errno;
-		unlink((char *) __stringVal(encodedNewPathName));
-		errno = eno;
-	    }
-	}
-#endif
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( false );
-	}
-	RETURN (true);
+        ret = link((char *) __stringVal(encodedOldPathName), (char *) __stringVal(encodedNewPathName));
+        if (ret >= 0) {
+            ret = unlink((char *) __stringVal(encodedOldPathName));
+            if (ret < 0) {
+                eno = errno;
+                unlink((char *) __stringVal(encodedNewPathName));
+                errno = eno;
+            }
+        }
+#endif
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( false );
+        }
+        RETURN (true);
     }
 %}.
     ^ self primitiveFailed
@@ -4185,56 +4186,56 @@
     off_t truncateSize;
 
     if (!__isStringLike(encodedPathName))
-	goto getOutOfHere;
+        goto getOutOfHere;
 
     if (__isSmallInteger(newSize)) {
-	truncateSize = __intVal(newSize);
-	if (truncateSize < 0) {
-	    goto getOutOfHere;
-	}
+        truncateSize = __intVal(newSize);
+        if (truncateSize < 0) {
+            goto getOutOfHere;
+        }
     } else {
-	truncateSize = __signedLongIntVal(newSize);
-	if (truncateSize < 0) {
-	    goto getOutOfHere;
-	}
-	if (truncateSize == 0) {
-	    if (sizeof(truncateSize) == 8) {
-		if (__signedLong64IntVal(newSize, &truncateSize) == 0 || truncateSize < 0) {
-		    goto getOutOfHere;
-		}
-	    } else {
-		goto getOutOfHere;
-	    }
-	}
+        truncateSize = __signedLongIntVal(newSize);
+        if (truncateSize < 0) {
+            goto getOutOfHere;
+        }
+        if (truncateSize == 0) {
+            if (sizeof(truncateSize) == 8) {
+                if (__signedLong64IntVal(newSize, &truncateSize) == 0 || truncateSize < 0) {
+                    goto getOutOfHere;
+                }
+            } else {
+                goto getOutOfHere;
+            }
+        }
     }
 
 #if defined(HAS_TRUNCATE)
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = truncate((char *) __stringVal(encodedPathName), truncateSize);
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = truncate((char *) __stringVal(encodedPathName), truncateSize);
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
 #else
 # ifdef HAS_FTRUNCATE
     {
-	int fd;
-
-	do {
-	    fd = open((char *) __stringVal(encodedPathName), 2);
-	} while (fd < 0 && errno == EINTR);
-	if (fd < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( false );
-	}
-
-	ret = ftruncate(fd, truncateSize);
-	close(fd);
+        int fd;
+
+        do {
+            fd = open((char *) __stringVal(encodedPathName), 2);
+        } while (fd < 0 && errno == EINTR);
+        if (fd < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( false );
+        }
+
+        ret = ftruncate(fd, truncateSize);
+        close(fd);
     }
 # endif /* HAS_FTRUNCATE */
 #endif
     if (ret < 0) {
-	@global(LastErrorNumber) = __mkSmallInteger(errno);
-	RETURN ( false );
+        @global(LastErrorNumber) = __mkSmallInteger(errno);
+        RETURN ( false );
     }
     RETURN (true);
 getOutOfHere:;
@@ -4270,40 +4271,40 @@
 #   endif
 
     if (aSymbol == @symbol(readUser)) {
-	RETURN ( __mkSmallInteger(S_IRUSR) );
+        RETURN ( __mkSmallInteger(S_IRUSR) );
     }
     if (aSymbol == @symbol(writeUser)) {
-	RETURN ( __mkSmallInteger(S_IWUSR) );
+        RETURN ( __mkSmallInteger(S_IWUSR) );
     }
     if (aSymbol == @symbol(executeUser)) {
-	RETURN ( __mkSmallInteger(S_IXUSR) );
+        RETURN ( __mkSmallInteger(S_IXUSR) );
     }
     if (aSymbol == @symbol(readGroup)) {
-	RETURN ( __mkSmallInteger(S_IRGRP) );
+        RETURN ( __mkSmallInteger(S_IRGRP) );
     }
     if (aSymbol == @symbol(writeGroup)) {
-	RETURN ( __mkSmallInteger(S_IWGRP) );
+        RETURN ( __mkSmallInteger(S_IWGRP) );
     }
     if (aSymbol == @symbol(executeGroup)) {
-	RETURN ( __mkSmallInteger(S_IXGRP) );
+        RETURN ( __mkSmallInteger(S_IXGRP) );
     }
     if (aSymbol == @symbol(readOthers)) {
-	RETURN ( __mkSmallInteger(S_IROTH) );
+        RETURN ( __mkSmallInteger(S_IROTH) );
     }
     if (aSymbol == @symbol(writeOthers)) {
-	RETURN ( __mkSmallInteger(S_IWOTH) );
+        RETURN ( __mkSmallInteger(S_IWOTH) );
     }
     if (aSymbol == @symbol(executeOthers)) {
-	RETURN ( __mkSmallInteger(S_IXOTH) );
+        RETURN ( __mkSmallInteger(S_IXOTH) );
     }
     if (aSymbol == @symbol(setUid)) {
-	RETURN ( __mkSmallInteger(S_ISUID) );
+        RETURN ( __mkSmallInteger(S_ISUID) );
     }
     if (aSymbol == @symbol(setGid)) {
-	RETURN ( __mkSmallInteger(S_ISGID) );
+        RETURN ( __mkSmallInteger(S_ISGID) );
     }
     if (aSymbol == @symbol(removeOnlyByOwner)) {
-	RETURN ( __mkSmallInteger(S_ISVTX) );
+        RETURN ( __mkSmallInteger(S_ISVTX) );
     }
 %}.
     ^ self primitiveFailed
@@ -4322,7 +4323,7 @@
 
     "
      this could have been implemented as:
-	(self infoOf:aPathName) at:#mode
+        (self infoOf:aPathName) at:#mode
      but for huge directory searches the code below is faster
     "
 
@@ -4335,19 +4336,19 @@
 
     if (__isStringLike(encodedPathName)) {
 # ifdef TRACE_STAT_CALLS
-	printf("stat on '%s' for accessMode\n", __stringVal(encodedPathName));
-# endif
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = stat((char *) __stringVal(encodedPathName), &buf);
-	} while ((ret < 0) && (errno == EINTR));
-	__END_INTERRUPTABLE__
-
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( nil );
-	}
-	RETURN ( __mkSmallInteger(buf.st_mode & 0777) );
+        printf("stat on '%s' for accessMode\n", __stringVal(encodedPathName));
+# endif
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = stat((char *) __stringVal(encodedPathName), &buf);
+        } while ((ret < 0) && (errno == EINTR));
+        __END_INTERRUPTABLE__
+
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( nil );
+        }
+        RETURN ( __mkSmallInteger(buf.st_mode & 0777) );
     }
 %}.
    ^ self primitiveFailed
@@ -4369,26 +4370,26 @@
 
     if (__isSmallInteger(aFileDescriptor)) {
 # ifdef TRACE_STAT_CALLS
-	printf("fstat on '%d' for accessMode\n", __smallIntegerVal(aFileDescriptor));
-# endif
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = fstat(__smallIntegerVal(aFileDescriptor), &buf);
-	} while ((ret < 0) && (errno == EINTR));
-	__END_INTERRUPTABLE__
-
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( nil );
-	}
-	RETURN ( __mkSmallInteger(buf.st_mode & 0777) );
+        printf("fstat on '%d' for accessMode\n", __smallIntegerVal(aFileDescriptor));
+# endif
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = fstat(__smallIntegerVal(aFileDescriptor), &buf);
+        } while ((ret < 0) && (errno == EINTR));
+        __END_INTERRUPTABLE__
+
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( nil );
+        }
+        RETURN ( __mkSmallInteger(buf.st_mode & 0777) );
     }
 %}.
    ^ self primitiveFailed
 
    "
     '/' asFilename readingFileDo:[:s|
-	(OperatingSystem accessModeOfFd:s fileDescriptor) printStringRadix:8
+        (OperatingSystem accessModeOfFd:s fileDescriptor) printStringRadix:8
     ].
    "
 !
@@ -4406,16 +4407,16 @@
     int ret;
 
     if (__isStringLike(encodedPathName) && __isSmallInteger(modeBits)) {
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = chmod((char *)__stringVal(encodedPathName), __intVal(modeBits));
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( false );
-	}
-	RETURN ( true );
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = chmod((char *)__stringVal(encodedPathName), __intVal(modeBits));
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( false );
+        }
+        RETURN ( true );
     }
 %}.
     ^ self primitiveFailed
@@ -4432,16 +4433,16 @@
     int ret;
 
     if (__isSmallInteger(aFileDescriptor) && __isSmallInteger(modeBits)) {
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = fchmod(__smallIntegerVal(aFileDescriptor), __intVal(modeBits));
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( false );
-	}
-	RETURN ( true );
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = fchmod(__smallIntegerVal(aFileDescriptor), __intVal(modeBits));
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( false );
+        }
+        RETURN ( true );
     }
 %}.
     ^ self primitiveFailed
@@ -4470,69 +4471,69 @@
 
 %{
     if (__isSmallInteger(aFileDescriptor)) {
-	int fd = __intVal(aFileDescriptor);
-	int lockArg;
-
-	/*
-	 * claus: sigh - each one has a different interface ...
-	 */
+        int fd = __intVal(aFileDescriptor);
+        int lockArg;
+
+        /*
+         * claus: sigh - each one has a different interface ...
+         */
 #if defined(F_SETLK)
-	{
-	    /*
-	     * new fcntl(SETLK) interface;
-	     * available on SYSV4 and Linux
-	     */
-	    struct flock flock;
-
-	    if (isSharedReadLock == true) {
-		flock.l_type = F_RDLCK;
-	    } else {
-		flock.l_type = F_WRLCK;
-	    }
-	    flock.l_whence = 0;
-	    flock.l_start = 0;
-	    flock.l_len = 0;
-	    lockArg = F_SETLK;
+        {
+            /*
+             * new fcntl(SETLK) interface;
+             * available on SYSV4 and Linux
+             */
+            struct flock flock;
+
+            if (isSharedReadLock == true) {
+                flock.l_type = F_RDLCK;
+            } else {
+                flock.l_type = F_WRLCK;
+            }
+            flock.l_whence = 0;
+            flock.l_start = 0;
+            flock.l_len = 0;
+            lockArg = F_SETLK;
 # if defined(F_SETLKW)
-	    if (blockIfLocked == true) {
-		lockArg = F_SETLKW;
-	    }
-# endif
-	    if (fcntl(fd, lockArg, &flock) != -1) {
-		RETURN (true);
-	    }
-	}
+            if (blockIfLocked == true) {
+                lockArg = F_SETLKW;
+            }
+# endif
+            if (fcntl(fd, lockArg, &flock) != -1) {
+                RETURN (true);
+            }
+        }
 
 #else /* no F_SETLK available */
 
 # if defined(LOCK_EX) && defined(LOCK_UN)
-	/*
-	 * BSD 4.3 advisory locks
-	 */
-	lockArg = LOCK_EX;
+        /*
+         * BSD 4.3 advisory locks
+         */
+        lockArg = LOCK_EX;
 #  if defined(LOCK_SH)
-	if (isSharedReadLock == true) {
-	    lockArg = LOCK_SH
-	}
+        if (isSharedReadLock == true) {
+            lockArg = LOCK_SH
+        }
 #  endif
 #  if defined(LOCK_NB)
-	if (blockIfLocked == false) {
-	    lockArg |= LOCK_NB;
-	}
-#  endif
-	if (flock(fd, lockArg) != -1) {
-	    RETURN (true);
-	}
+        if (blockIfLocked == false) {
+            lockArg |= LOCK_NB;
+        }
+#  endif
+        if (flock(fd, lockArg) != -1) {
+            RETURN (true);
+        }
 
 # else /* no flock available */
 
 #  if defined(F_LOCK) && defined(F_UNLOCK)
-	/*
-	 * SYSV3 advisory locks
-	 */
-	if (lockf(fd, F_LOCK, 0) != -1) {
-	    RETURN (true);
-	}
+        /*
+         * SYSV3 advisory locks
+         */
+        if (lockf(fd, F_LOCK, 0) != -1) {
+            RETURN (true);
+        }
 #  endif
 # endif
 #endif
@@ -4624,47 +4625,47 @@
 
 %{
     if (__isSmallInteger(aFileDescriptor)) {
-	int fd = __intVal(aFileDescriptor);
-
-	/*
-	 * claus: sigh - each one has a different interface ...
-	 */
+        int fd = __intVal(aFileDescriptor);
+
+        /*
+         * claus: sigh - each one has a different interface ...
+         */
 #if defined(F_SETLK)
-	{
-	    /*
-	     * new fcntl(SETLK) interface;
-	     * available on SYSV4 and Linux
-	     */
-	    struct flock flock;
-
-	    flock.l_type = F_UNLCK;
-	    flock.l_whence = 0;
-	    flock.l_start = 0;
-	    flock.l_len = 0;
-	    if (fcntl(fd, F_SETLK, &flock) != -1) {
-		RETURN (true);
-	    }
-	}
+        {
+            /*
+             * new fcntl(SETLK) interface;
+             * available on SYSV4 and Linux
+             */
+            struct flock flock;
+
+            flock.l_type = F_UNLCK;
+            flock.l_whence = 0;
+            flock.l_start = 0;
+            flock.l_len = 0;
+            if (fcntl(fd, F_SETLK, &flock) != -1) {
+                RETURN (true);
+            }
+        }
 
 #else /* no F_SETLK available */
 
 # if defined(LOCK_EX) && defined(LOCK_UN)
-	/*
-	 * BSD 4.3 advisory locks
-	 */
-	if (flock(fd, LOCK_UN) != -1) {
-	    RETURN (true);
-	}
+        /*
+         * BSD 4.3 advisory locks
+         */
+        if (flock(fd, LOCK_UN) != -1) {
+            RETURN (true);
+        }
 
 # else /* no flock available */
 
 #  if defined(F_LOCK) && defined(F_UNLOCK)
-	/*
-	 * SYSV3 advisory locks
-	 */
-	if (lockf(fd, F_UNLOCK, 0) != -1) {
-	    RETURN (true);
-	}
+        /*
+         * SYSV3 advisory locks
+         */
+        if (lockf(fd, F_UNLOCK, 0) != -1) {
+            RETURN (true);
+        }
 #  endif
 # endif
 #endif
@@ -4696,27 +4697,27 @@
     |names n "{ Class: SmallInteger }" |
 
     names := pathName
-		asCollectionOfSubstringsSeparatedBy:self fileSeparator.
+                asCollectionOfSubstringsSeparatedBy:self fileSeparator.
     names := names asOrderedCollection.
     "
      cut off initial double-slashes
     "
     [names startsWith:#('' '')] whileTrue:[
-	names removeFirst.
+        names removeFirst.
     ].
     "
      cut off double-slashes at end
     "
     [names endsWith:#('')] whileTrue:[
-	names removeLast.
+        names removeLast.
     ].
     "
      cut off current-dir at beginning
     "
     n := names size.
     [(n >= 2) and:[names startsWith:#('.')]] whileTrue:[
-	names removeFirst.
-	n := n - 1.
+        names removeFirst.
+        n := n - 1.
     ].
 
     "
@@ -4725,14 +4726,14 @@
     [(n > 2)
      and:[(names endsWith:#('..'))
      and:[((names at:(n - 1)) startsWith:'.') not ]]] whileTrue:[
-	names removeLast; removeLast.
-	n := n - 2.
+        names removeLast; removeLast.
+        n := n - 2.
     ].
 
     ^ names asStringWith:self fileSeparator
-		    from:1
-		    to:n
-		    compressTabs:false final:nil
+                    from:1
+                    to:n
+                    compressTabs:false final:nil
 
     "
      OperatingSystem compressPath:'./..'
@@ -4768,7 +4769,7 @@
     ^ path.
 
     "
-	self getCurrentDirectory
+        self getCurrentDirectory
     "
 !
 
@@ -4777,8 +4778,8 @@
      The amountof information returned depends upon the OS, and is
      not guaranteed to be consistent across architectures.
      On unix, the information returned is (at least):
-	freeBytes
-	totalBytes
+        freeBytes
+        totalBytes
     "
 
     |outputText keys values n info
@@ -4809,22 +4810,22 @@
 
     n := Integer readFrom:(values at:capacityIdx) onError:nil.
     n notNil ifTrue:[
-	info at:#percentUsed put:n
+        info at:#percentUsed put:n
     ].
 
     n := Integer readFrom:(values at:availIdx) onError:nil.
     n notNil ifTrue:[
-	info at:#freeBytes put:(n * 1024)
+        info at:#freeBytes put:(n * 1024)
     ].
 
     n := Integer readFrom:(values at:usedIdx) onError:nil.
     n notNil ifTrue:[
-	info at:#usedBytes put:(n * 1024)
+        info at:#usedBytes put:(n * 1024)
     ].
 
     n := Integer readFrom:(values at:sizeIdx) onError:nil.
     n notNil ifTrue:[
-	info at:#totalBytes put:(n * 1024)
+        info at:#totalBytes put:(n * 1024)
     ].
 
     info at:#mountPoint put:(values at:mountIdx).
@@ -4852,9 +4853,9 @@
     "/ root, home and current directories.
     "/
     ^ Array
-	with:'/'
-	with:(self getHomeDirectory)
-	with:(Filename currentDirectory pathName)
+        with:'/'
+        with:(self getHomeDirectory)
+        with:(Filename currentDirectory pathName)
 
     "Modified: / 5.6.1998 / 18:35:35 / cg"
 !
@@ -4864,8 +4865,8 @@
      The amount of information returned depends upon the OS, and is
      not guaranteed to be consistent across architectures.
      On unix, the information returned is (at least):
-	mountPoint - mount point
-	fileSystem - device or NFS-remotePath
+        mountPoint - mount point
+        fileSystem - device or NFS-remotePath
     "
 
     |outputText keys values info infoEntry|
@@ -4883,15 +4884,15 @@
     info := OrderedCollection new.
 
     outputText from:2 do:[:line |
-	values := line asCollectionOfWords.
-
-	values size >= 2 ifTrue:[
-
-	    infoEntry := IdentityDictionary new.
-	    infoEntry at:#mountPoint put:(values last).
-	    infoEntry at:#fileSystem put:(values first).
-	    info add:infoEntry.
-	]
+        values := line asCollectionOfWords.
+
+        values size >= 2 ifTrue:[
+
+            infoEntry := IdentityDictionary new.
+            infoEntry at:#mountPoint put:(values last).
+            infoEntry at:#fileSystem put:(values first).
+            info add:infoEntry.
+        ]
     ].
     ^ info
 
@@ -4915,9 +4916,9 @@
 
      The info object returned is OS-specific, however it responds to at
      least
-	#isFor32BitArchitecture
-	#isFor64BitArchitecture ... returns true, if the given object is for
-				     32bit, 64bit architecture respectively
+        #isFor32BitArchitecture
+        #isFor64BitArchitecture ... returns true, if the given object is for
+                                     32bit, 64bit architecture respectively
     "
     ^ ELFFileHeader fromFile: aStringOrFilename
 
@@ -4928,21 +4929,21 @@
     "return some object filled with info for the file 'aPathName';
      the info (for which corresponding access methods are understood by
      the returned object) is:
-	 type            - a symbol giving the files type
-	 mode            - numeric access mode
-	 uid             - owners user id
-	 gid             - owners group id
-	 size            - files size
-	 id              - files number (i.e. inode number)
-	 accessed        - last access time (as Timestamp)
-	 modified        - last modification time (as Timestamp)
-	 statusChanged   - last status change time (as Timestamp)
-	 alternativeName     - (windows only:) the MSDOS name of the file
-	 recordFormatNumeric - (VMS only:) numeric value of the recordFormat
-	 recordFormat        - (VMS only:) symbolic value of the recordFormat
-	 recordAttributes    - (VMS only:) recordAttributes
-	 fixedHeaderSize     - (VMS only:) fixed header size in a variable record format
-	 recordSize          - (VMS only:) record size.
+         type            - a symbol giving the files type
+         mode            - numeric access mode
+         uid             - owners user id
+         gid             - owners group id
+         size            - files size
+         id              - files number (i.e. inode number)
+         accessed        - last access time (as Timestamp)
+         modified        - last modification time (as Timestamp)
+         statusChanged   - last status change time (as Timestamp)
+         alternativeName     - (windows only:) the MSDOS name of the file
+         recordFormatNumeric - (VMS only:) numeric value of the recordFormat
+         recordFormat        - (VMS only:) symbolic value of the recordFormat
+         recordAttributes    - (VMS only:) recordAttributes
+         fixedHeaderSize     - (VMS only:) fixed header size in a variable record format
+         recordSize          - (VMS only:) record size.
 
      Some of the fields may be returned as nil on systems which do not provide
      all of the information.
@@ -4960,8 +4961,8 @@
     int ret;
 
     if (!__isStringLike(encodedPathName)) {
-	error = @symbol(badArgument);
-	goto out;
+        error = @symbol(badArgument);
+        goto out;
     }
 
 # ifdef TRACE_STAT_CALLS
@@ -4969,76 +4970,76 @@
 # endif
     __BEGIN_INTERRUPTABLE__
     do {
-	ret = stat((char *) __stringVal(encodedPathName), &buf);
+        ret = stat((char *) __stringVal(encodedPathName), &buf);
     } while ((ret < 0) && (errno == EINTR));
     __END_INTERRUPTABLE__
 
     if (ret < 0) {
-	error = __mkSmallInteger(errno);
-	@global(LastErrorNumber) = error;
-	goto out;
+        error = __mkSmallInteger(errno);
+        @global(LastErrorNumber) = error;
+        goto out;
     }
     switch (buf.st_mode & S_IFMT) {
-	case S_IFDIR:
-	    type = @symbol(directory);
-	    break;
-
-	case S_IFREG:
-	    type = @symbol(regular);
-	    break;
+        case S_IFDIR:
+            type = @symbol(directory);
+            break;
+
+        case S_IFREG:
+            type = @symbol(regular);
+            break;
 # ifdef S_IFCHR
-	case S_IFCHR:
-	    type = @symbol(characterSpecial);
-	    break;
+        case S_IFCHR:
+            type = @symbol(characterSpecial);
+            break;
 # endif
 # ifdef S_IFBLK
-	case S_IFBLK:
-	    type = @symbol(blockSpecial);
-	    break;
+        case S_IFBLK:
+            type = @symbol(blockSpecial);
+            break;
 # endif
 # ifdef S_IFMPC
-	case S_IFMPC:
-	    type = @symbol(multiplexedCharacterSpecial);
-	    break;
+        case S_IFMPC:
+            type = @symbol(multiplexedCharacterSpecial);
+            break;
 # endif
 # ifdef S_IFMPB
-	case S_IFMPB:
-	    type = @symbol(multiplexedBlockSpecial);
-	    break;
+        case S_IFMPB:
+            type = @symbol(multiplexedBlockSpecial);
+            break;
 # endif
 # ifdef S_IFLNK
-	case S_IFLNK:
-	    type = @symbol(symbolicLink);
-	    break;
+        case S_IFLNK:
+            type = @symbol(symbolicLink);
+            break;
 # endif
 # ifdef S_IFSOCK
-	case S_IFSOCK:
-	    type = @symbol(socket);
-	    break;
+        case S_IFSOCK:
+            type = @symbol(socket);
+            break;
 # endif
 # ifdef S_IFIFO
-	case S_IFIFO:
-	    type = @symbol(fifo);
-	    break;
-# endif
-	default:
-	    type = @symbol(unknown);
-	    break;
+        case S_IFIFO:
+            type = @symbol(fifo);
+            break;
+# endif
+        default:
+            type = @symbol(unknown);
+            break;
     }
 
     if (sizeof(buf.st_ino) == 8) {
-	id = __MKUINT64(&buf.st_ino);
+        id = __MKUINT64(&buf.st_ino);
     } else {
-	id = __MKUINT(buf.st_ino);
+        id = __MKUINT(buf.st_ino);
     }
     mode = __mkSmallInteger(buf.st_mode & 0777);
     uid = __mkSmallInteger(buf.st_uid);
     gid = __mkSmallInteger(buf.st_gid);
     nLink = __mkSmallInteger(buf.st_nlink);
     if (sizeof(buf.st_size) == 8) {
-	size = __MKINT64(&buf.st_size);
+        size = __MKINT64(&buf.st_size);
     } else {
-	size = __MKINT(buf.st_size);
+        size = __MKINT(buf.st_size);
     }
     aOStime = __MKUINT(buf.st_atime);
     mOStime = __MKUINT(buf.st_mtime);
@@ -5047,26 +5048,26 @@
     out:;
 %}.
      mode notNil ifTrue:[
-	"/ now done lazy in FileStatusInfo
-	"/ atime := Timestamp fromOSTime:(aOStime * 1000).
-	"/ mtime := Timestamp fromOSTime:(mOStime * 1000).
-	"/ ctime := Timestamp fromOSTime:(cOStime * 1000).
-
-	^ FileStatusInfo
-		    type:type
-		    mode:mode
-		    uid:uid
-		    gid:gid
-		    size:size
-		    id:id
-		    accessed:aOStime
-		    modified:mOStime
-		    statusChanged:cOStime
-		    sourcePath:nil targetPath:nil
-		    numLinks:nLink.
+        "/ now done lazy in FileStatusInfo
+        "/ atime := Timestamp fromOSTime:(aOStime * 1000).
+        "/ mtime := Timestamp fromOSTime:(mOStime * 1000).
+        "/ ctime := Timestamp fromOSTime:(cOStime * 1000).
+
+        ^ FileStatusInfo
+                    type:type
+                    mode:mode
+                    uid:uid
+                    gid:gid
+                    size:size
+                    id:id
+                    accessed:aOStime
+                    modified:mOStime
+                    statusChanged:cOStime
+                    sourcePath:nil targetPath:nil
+                    numLinks:nLink.
     ].
     error notNil ifTrue:[
-	^ nil.
+        ^ nil.
     ].
 
     ^ self primitiveFailed
@@ -5091,40 +5092,40 @@
 %{
 #ifdef __SCHTEAM__
     if (encodedPathName.isStringLike()) {
-	java.io.File file = new java.io.File( encodedPathName.asString() );
-	int _mode;
-
-	if (file.exists() && file.isDirectory()) {
-	    return __c__._RETURN_true();
-	}
-	return __c__._RETURN_false();
+        java.io.File file = new java.io.File( encodedPathName.asString() );
+        int _mode;
+
+        if (file.exists() && file.isDirectory()) {
+            return __c__._RETURN_true();
+        }
+        return __c__._RETURN_false();
     }
 #else
     int ret;
 
     if (__isStringLike(encodedPathName)) {
-	struct stat buf;
+        struct stat buf;
 
 # ifdef TRACE_STAT_CALLS
-	printf("stat on '%s' for isDirectory\n", __stringVal(encodedPathName));
-# endif
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = stat((char *) __stringVal(encodedPathName), &buf);
-	} while ((ret < 0) && (errno == EINTR));
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( false );
-	}
-	RETURN ( ((buf.st_mode & S_IFMT) == S_IFDIR) ? true : false);
+        printf("stat on '%s' for isDirectory\n", __stringVal(encodedPathName));
+# endif
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = stat((char *) __stringVal(encodedPathName), &buf);
+        } while ((ret < 0) && (errno == EINTR));
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( false );
+        }
+        RETURN ( ((buf.st_mode & S_IFMT) == S_IFDIR) ? true : false);
     }
 #endif /* not SCHTEAM */
 %}.
     ^ self primitiveFailed
 
     "an alternative implementation would be:
-	^ (self infoOf:aPathName) type == #directory
+        ^ (self infoOf:aPathName) type == #directory
     "
 !
 
@@ -5139,30 +5140,30 @@
 %{
 #ifdef __SCHTEAM__
     if (encodedPathName.isStringLike()) {
-	java.io.File file = new java.io.File( encodedPathName.asString() );
-	int _mode;
-
-	if (file.exists() && file.canExecute()) {
-	    return __c__._RETURN_true();
-	}
-	return __c__._RETURN_false();
+        java.io.File file = new java.io.File( encodedPathName.asString() );
+        int _mode;
+
+        if (file.exists() && file.canExecute()) {
+            return __c__._RETURN_true();
+        }
+        return __c__._RETURN_false();
     }
 #else
     int ret;
 
     if (__isStringLike(encodedPathName)) {
 # ifdef TRACE_ACCESS_CALLS
-	printf("access on '%s' for executable\n", __stringVal(encodedPathName));
-# endif
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = access(__stringVal(encodedPathName), X_OK);
-	} while ((ret < 0) && (errno == EINTR));
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	}
-	RETURN ( ((ret == 0) ? true : false) );
+        printf("access on '%s' for executable\n", __stringVal(encodedPathName));
+# endif
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = access(__stringVal(encodedPathName), X_OK);
+        } while ((ret < 0) && (errno == EINTR));
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+        }
+        RETURN ( ((ret == 0) ? true : false) );
     }
 #endif /* not SCHTEAM */
 %}.
@@ -5179,30 +5180,30 @@
 %{
 #ifdef __SCHTEAM__
     if (encodedPathName.isStringLike()) {
-	java.io.File file = new java.io.File( encodedPathName.asString() );
-	int _mode;
-
-	if (file.exists() && file.canRead()) {
-	    return __c__._RETURN_true();
-	}
-	return __c__._RETURN_false();
+        java.io.File file = new java.io.File( encodedPathName.asString() );
+        int _mode;
+
+        if (file.exists() && file.canRead()) {
+            return __c__._RETURN_true();
+        }
+        return __c__._RETURN_false();
     }
 #else
     int ret;
 
     if (__isStringLike(encodedPathName)) {
 # ifdef TRACE_ACCESS_CALLS
-	printf("access on '%s' for readable\n", __stringVal(encodedPathName));
-# endif
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = access(__stringVal(encodedPathName), R_OK);
-	} while ((ret < 0) && (errno == EINTR));
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	}
-	RETURN ( ((ret == 0) ? true : false) );
+        printf("access on '%s' for readable\n", __stringVal(encodedPathName));
+# endif
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = access(__stringVal(encodedPathName), R_OK);
+        } while ((ret < 0) && (errno == EINTR));
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+        }
+        RETURN ( ((ret == 0) ? true : false) );
     }
 #endif /* not SCHTEAM */
 %}.
@@ -5219,13 +5220,13 @@
 %{
 #ifdef __SCHTEAM__
     if (encodedPathName.isStringLike()) {
-	java.io.File file = new java.io.File( encodedPathName.asString() );
-	int _mode;
-
-	if (file.exists()) {
-	    return __c__._RETURN_true();
-	}
-	return __c__._RETURN_false();
+        java.io.File file = new java.io.File( encodedPathName.asString() );
+        int _mode;
+
+        if (file.exists()) {
+            return __c__._RETURN_true();
+        }
+        return __c__._RETURN_false();
     }
 #else
     struct stat buf;
@@ -5233,18 +5234,18 @@
 
     if (__isStringLike(encodedPathName)) {
 # ifdef TRACE_STAT_CALLS
-	printf("stat on '%s' for isValidPath\n", __stringVal(encodedPathName));
-# endif
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = stat((char *) __stringVal(encodedPathName), &buf);
-	} while ((ret < 0) && (errno == EINTR));
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN (false);
-	}
-	RETURN ( ret ? false : true );
+        printf("stat on '%s' for isValidPath\n", __stringVal(encodedPathName));
+# endif
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = stat((char *) __stringVal(encodedPathName), &buf);
+        } while ((ret < 0) && (errno == EINTR));
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN (false);
+        }
+        RETURN ( ret ? false : true );
     }
 #endif /* not SCHTEAM */
 %}.
@@ -5264,30 +5265,30 @@
 %{
 #ifdef __SCHTEAM__
     if (encodedPathName.isStringLike()) {
-	java.io.File file = new java.io.File( encodedPathName.asString() );
-	int _mode;
-
-	if (file.exists() && file.canWrite()) {
-	    return __c__._RETURN_true();
-	}
-	return __c__._RETURN_false();
+        java.io.File file = new java.io.File( encodedPathName.asString() );
+        int _mode;
+
+        if (file.exists() && file.canWrite()) {
+            return __c__._RETURN_true();
+        }
+        return __c__._RETURN_false();
     }
 #else
     int ret;
 
     if (__isStringLike(encodedPathName)) {
 # ifdef TRACE_ACCESS_CALLS
-	printf("access on '%s' for writable\n", __stringVal(encodedPathName));
-# endif
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = access(__stringVal(encodedPathName), W_OK);
-	} while ((ret < 0) && (errno == EINTR));
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	}
-	RETURN ( ((ret == 0) ? true : false) );
+        printf("access on '%s' for writable\n", __stringVal(encodedPathName));
+# endif
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = access(__stringVal(encodedPathName), W_OK);
+        } while ((ret < 0) && (errno == EINTR));
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+        }
+        RETURN ( ((ret == 0) ? true : false) );
     }
 #endif /* not SCHTEAM */
 %}.
@@ -5299,21 +5300,21 @@
 
      The info (for which corresponding access methods are understood by
      the returned object) is:
-	 type            - a symbol giving the file's type
-	 mode            - numeric access mode
-	 uid             - owners user id
-	 gid             - owners group id
-	 size            - files size
-	 id              - files number (i.e. inode number)
-	 accessed        - last access time (as Timestamp)
-	 modified        - last modification time (as Timestamp)
-	 statusChanged   - last status change time (as Timestamp)
-	 alternativeName     - (windows only:) the MSDOS name of the file
-	 recordFormatNumeric - (VMS only:) numeric value of the recordFormat
-	 recordFormat        - (VMS only:) symbolic value of the recordFormat
-	 recordAttributes    - (VMS only:) recordAttributes
-	 fixedHeaderSize     - (VMS only:) fixed header size in a variable record format
-	 recordSize          - (VMS only:) record size.
+         type            - a symbol giving the file's type
+         mode            - numeric access mode
+         uid             - owners user id
+         gid             - owners group id
+         size            - files size
+         id              - files number (i.e. inode number)
+         accessed        - last access time (as Timestamp)
+         modified        - last modification time (as Timestamp)
+         statusChanged   - last status change time (as Timestamp)
+         alternativeName     - (windows only:) the MSDOS name of the file
+         recordFormatNumeric - (VMS only:) numeric value of the recordFormat
+         recordFormat        - (VMS only:) symbolic value of the recordFormat
+         recordAttributes    - (VMS only:) recordAttributes
+         fixedHeaderSize     - (VMS only:) fixed header size in a variable record format
+         recordSize          - (VMS only:) record size.
 
      Some of the fields may be returned as nil on systems which do not provide
      all of the information.
@@ -5333,35 +5334,35 @@
 %{  /* STACK: 1200 */
 #ifdef __SCHTEAM__
     if (encodedPathName.isStringLike()) {
-	java.io.File file = new java.io.File( encodedPathName.asString() );
-	int _mode;
-
-	if (file.isDirectory()) {
-	    type = STSymbol._new("directory");
-	} else if (file.isFile()) {
-	    type = STSymbol._new("regular");
-	} else {
-	    type = STSymbol._new("unknown");
-	}
-	_mode = 0;
-	if (file.canRead()) {
-	    _mode |= 0444;
-	}
-	if (file.canWrite()) {
-	    _mode |= 0222;
-	}
-	if (file.canExecute()) {
-	    _mode |= 0111;
-	}
-	mode = STInteger._new( _mode );
-	uid = STInteger._0;
-	gid = STInteger._0;
-	nLink = STInteger._0;
-	size = STInteger._new( file.length());
-	aOStime = STInteger._new( file.lastModified() );
-	mOStime = STInteger._new( file.lastModified() );
-	cOStime = STInteger._new( file.lastModified() );
-	path = new STString( file.getPath() );
+        java.io.File file = new java.io.File( encodedPathName.asString() );
+        int _mode;
+
+        if (file.isDirectory()) {
+            type = STSymbol._new("directory");
+        } else if (file.isFile()) {
+            type = STSymbol._new("regular");
+        } else {
+            type = STSymbol._new("unknown");
+        }
+        _mode = 0;
+        if (file.canRead()) {
+            _mode |= 0444;
+        }
+        if (file.canWrite()) {
+            _mode |= 0222;
+        }
+        if (file.canExecute()) {
+            _mode |= 0111;
+        }
+        mode = STInteger._new( _mode );
+        uid = STInteger._0;
+        gid = STInteger._0;
+        nLink = STInteger._0;
+        size = STInteger._new( file.length());
+        aOStime = STInteger._new( file.lastModified() );
+        mOStime = STInteger._new( file.lastModified() );
+        cOStime = STInteger._new( file.lastModified() );
+        path = new STString( file.getPath() );
     }
 #else
     struct stat buf;
@@ -5369,104 +5370,104 @@
     char pathBuffer[1024];
 
     if (__isStringLike(encodedPathName)) {
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = lstat((char *) __stringVal(encodedPathName), &buf);
-	} while ((ret < 0) && (errno == EINTR));
-	__END_INTERRUPTABLE__
-
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( nil );
-	}
-	switch (buf.st_mode & S_IFMT) {
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = lstat((char *) __stringVal(encodedPathName), &buf);
+        } while ((ret < 0) && (errno == EINTR));
+        __END_INTERRUPTABLE__
+
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( nil );
+        }
+        switch (buf.st_mode & S_IFMT) {
 # ifdef S_IFLNK
-	    case S_IFLNK:
-		type = @symbol(symbolicLink);
-		if ((ret = readlink((char *) __stringVal(encodedPathName), pathBuffer, sizeof(pathBuffer))) < 0) {
-		    @global(LastErrorNumber) = __mkSmallInteger(errno);
-		    RETURN ( nil );
-		}
-		pathBuffer[ret] = '\0';  /* readlink does not 0-terminate */
-		path = __MKSTRING(pathBuffer);
-		break;
-# endif
-	    case S_IFDIR:
-		type = @symbol(directory);
-		break;
-
-	    case S_IFREG:
-		type = @symbol(regular);
-		break;
+            case S_IFLNK:
+                type = @symbol(symbolicLink);
+                if ((ret = readlink((char *) __stringVal(encodedPathName), pathBuffer, sizeof(pathBuffer))) < 0) {
+                    @global(LastErrorNumber) = __mkSmallInteger(errno);
+                    RETURN ( nil );
+                }
+                pathBuffer[ret] = '\0';  /* readlink does not 0-terminate */
+                path = __MKSTRING(pathBuffer);
+                break;
+# endif
+            case S_IFDIR:
+                type = @symbol(directory);
+                break;
+
+            case S_IFREG:
+                type = @symbol(regular);
+                break;
 # ifdef S_IFCHR
-	    case S_IFCHR:
-		type = @symbol(characterSpecial);
-		break;
+            case S_IFCHR:
+                type = @symbol(characterSpecial);
+                break;
 # endif
 # ifdef S_IFBLK
-	    case S_IFBLK:
-		type = @symbol(blockSpecial);
-		break;
+            case S_IFBLK:
+                type = @symbol(blockSpecial);
+                break;
 # endif
 # ifdef S_IFMPC
-	    case S_IFMPC:
-		type = @symbol(multiplexedCharacterSpecial);
-		break;
+            case S_IFMPC:
+                type = @symbol(multiplexedCharacterSpecial);
+                break;
 # endif
 # ifdef S_IFMPB
-	    case S_IFMPB:
-		type = @symbol(multiplexedBlockSpecial);
-		break;
+            case S_IFMPB:
+                type = @symbol(multiplexedBlockSpecial);
+                break;
 # endif
 # ifdef S_IFSOCK
-	    case S_IFSOCK:
-		type = @symbol(socket);
-		break;
+            case S_IFSOCK:
+                type = @symbol(socket);
+                break;
 # endif
 # ifdef S_IFIFO
-	    case S_IFIFO:
-		type = @symbol(fifo);
-		break;
-# endif
-	    default:
-		type = @symbol(unknown);
-		break;
-	}
-
-	if (sizeof(buf.st_ino) == 8) {
-	    id = __MKUINT64(&buf.st_ino);
-	} else {
-	    id = __MKUINT(buf.st_ino);
-	}
-	mode = __mkSmallInteger(buf.st_mode & 0777);
-	uid = __mkSmallInteger(buf.st_uid);
-	gid = __mkSmallInteger(buf.st_gid);
-	nLink = __mkSmallInteger(buf.st_nlink);
-	if (sizeof(buf.st_size) == 8) {
-	    size = __MKINT64(&buf.st_size);
-	} else {
-	    size = __MKINT(buf.st_size);
-	}
-	aOStime = __MKUINT(buf.st_atime);
-	mOStime = __MKUINT(buf.st_mtime);
-	cOStime = __MKUINT(buf.st_ctime);
+            case S_IFIFO:
+                type = @symbol(fifo);
+                break;
+# endif
+            default:
+                type = @symbol(unknown);
+                break;
+        }
+
+        if (sizeof(buf.st_ino) == 8) {
+            id = __MKUINT64(&buf.st_ino);
+        } else {
+            id = __MKUINT(buf.st_ino);
+        }
+        mode = __mkSmallInteger(buf.st_mode & 0777);
+        uid = __mkSmallInteger(buf.st_uid);
+        gid = __mkSmallInteger(buf.st_gid);
+        nLink = __mkSmallInteger(buf.st_nlink);
+        if (sizeof(buf.st_size) == 8) {
+            size = __MKINT64(&buf.st_size);
+        } else {
+            size = __MKINT(buf.st_size);
+        }
+        aOStime = __MKUINT(buf.st_atime);
+        mOStime = __MKUINT(buf.st_mtime);
+        cOStime = __MKUINT(buf.st_ctime);
     }
 #endif /* not SCHTEAM */
 %}.
 
     mode notNil ifTrue:[
-	^ FileStatusInfo
-	    type:type
-	    mode:mode
-	    uid:uid
-	    gid:gid
-	    size:size
-	    id:id
-	    accessed:aOStime
-	    modified:mOStime
-	    statusChanged:cOStime
-	    sourcePath:aPathName targetPath:(self decodePath:path)
-	    numLinks:nLink.
+        ^ FileStatusInfo
+            type:type
+            mode:mode
+            uid:uid
+            gid:gid
+            size:size
+            id:id
+            accessed:aOStime
+            modified:mOStime
+            statusChanged:cOStime
+            sourcePath:aPathName targetPath:(self decodePath:path)
+            numLinks:nLink.
    ].
    ^ self primitiveFailed
 
@@ -5483,15 +5484,15 @@
      the info is cached for some time (5 minutes)"
 
     CacheMountPointsTimeStamp notNil ifTrue:[
-	Timestamp now < (CacheMountPointsTimeStamp addSeconds:5*60) ifTrue:[
-	    ^ CachedMountPoints
-	].
+        Timestamp now < (CacheMountPointsTimeStamp addSeconds:5*60) ifTrue:[
+            ^ CachedMountPoints
+        ].
     ].
 
     '/proc/mounts' asFilename exists ifTrue:[
-	CachedMountPoints := self mountPointsFromProcFS.
-	CacheMountPointsTimeStamp := Timestamp now.
-	^ CachedMountPoints
+        CachedMountPoints := self mountPointsFromProcFS.
+        CacheMountPointsTimeStamp := Timestamp now.
+        ^ CachedMountPoints
     ].
 
     "/ TODO: add fallback code for other OS's (i.e. reading /etc/mtab)
@@ -5532,66 +5533,66 @@
     |p path command|
 
     path = '.' ifTrue:[
-	^ self getCurrentDirectory.
+        ^ self getCurrentDirectory.
     ].
 
     "some systems have a convenient function for this ..."
     path := self primPathNameOf:(self encodePath:pathName).
     path notNil ifTrue:[
-	path := self decodePath:path.
+        path := self decodePath:path.
     ] ifFalse:[
-	(self isValidPath:pathName) ifFalse:[
-	    p := pathName.
-	    [(p size > 1)
-	     and:[p endsWith:(self fileSeparator)]
-	    ] whileTrue:[
-		p := p copyButLast.
-	    ].
-	    ^ p
-	].
-
-	(SlowFork==true or:[PipeFailed==true]) ifFalse:[
-	    |directoryName fileBaseName|
-
-	    (self isDirectory:pathName) ifTrue:[
-		directoryName := pathName.
-		fileBaseName := nil.
-	    ] ifFalse:[
-		|pathFilename|
-		pathFilename := pathName asFilename.
-		directoryName := pathFilename directoryName.
-		fileBaseName := pathFilename baseName.
-	    ].
-
-	    PipeStream openErrorSignal handle:[:ex |
-		PipeFailed := true.
-		'UnixOperatingSystem [warning]: cannot fork/popen' errorPrintCR.
-		ex return.
-	    ] do:[
-		"have to fall back ..."
-		command := 'cd "' , directoryName , '"; pwd'.
-		p := PipeStream readingFrom:command.
-	    ].
-
-	    (p isNil or:[p atEnd]) ifTrue:[
-		('UnixOperatingSystem [warning]: PipeStream for <' , command , '> failed') errorPrintCR.
-	    ] ifFalse:[
-		path := p nextLine.
-		p close.
-	    ].
-	    fileBaseName notNil ifTrue:[
-		path := path, '/', fileBaseName.
-	    ].
-	].
-	path isNil ifTrue:[
-	    "/
-	    "/ return the original - there is nothing else can we do
-	    "/
-	    path := pathName
-	].
-	(SlowFork==true or:[ForkFailed==true]) ifTrue:[
-	    path := self compressPath:path
-	]
+        (self isValidPath:pathName) ifFalse:[
+            p := pathName.
+            [(p size > 1)
+             and:[p endsWith:(self fileSeparator)]
+            ] whileTrue:[
+                p := p copyButLast.
+            ].
+            ^ p
+        ].
+
+        (SlowFork==true or:[PipeFailed==true]) ifFalse:[
+            |directoryName fileBaseName|
+
+            (self isDirectory:pathName) ifTrue:[
+                directoryName := pathName.
+                fileBaseName := nil.
+            ] ifFalse:[
+                |pathFilename|
+                pathFilename := pathName asFilename.
+                directoryName := pathFilename directoryName.
+                fileBaseName := pathFilename baseName.
+            ].
+
+            PipeStream openErrorSignal handle:[:ex |
+                PipeFailed := true.
+                'UnixOperatingSystem [warning]: cannot fork/popen' errorPrintCR.
+                ex return.
+            ] do:[
+                "have to fall back ..."
+                command := 'cd "' , directoryName , '"; pwd'.
+                p := PipeStream readingFrom:command.
+            ].
+
+            (p isNil or:[p atEnd]) ifTrue:[
+                ('UnixOperatingSystem [warning]: PipeStream for <' , command , '> failed') errorPrintCR.
+            ] ifFalse:[
+                path := p nextLine.
+                p close.
+            ].
+            fileBaseName notNil ifTrue:[
+                path := path, '/', fileBaseName.
+            ].
+        ].
+        path isNil ifTrue:[
+            "/
+            "/ return the original - there is nothing else can we do
+            "/
+            path := pathName
+        ].
+        (SlowFork==true or:[ForkFailed==true]) ifTrue:[
+            path := self compressPath:path
+        ]
     ].
     ^ path.
 
@@ -5616,17 +5617,17 @@
     |path|
 
 %{  /* UNLIMITEDSTACK */
-	char nameBuffer[MAXPATHLEN + 1];
-
-	if (getcwd(nameBuffer, MAXPATHLEN)) {
-	    path = __MKSTRING(nameBuffer);
-	    RETURN(path);
-	}
+        char nameBuffer[MAXPATHLEN + 1];
+
+        if (getcwd(nameBuffer, MAXPATHLEN)) {
+            path = __MKSTRING(nameBuffer);
+            RETURN(path);
+        }
 %}.
     ^ self primitiveFailed.
 
     "
-	self primGetCurrentDirectory
+        self primGetCurrentDirectory
     "
 !
 
@@ -5644,20 +5645,20 @@
 
     if (__isStringLike(encodedPathName)) {
 # ifdef TRACE_STAT_CALLS
-	printf("stat on '%s' for id\n", __stringVal(encodedPathName));
-# endif
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = stat((char *) __stringVal(encodedPathName), &buf);
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
-	if (ret >= 0) {
-	    ino = buf.st_ino;
-	    retVal = __MKUINT(ino);
-	    RETURN (retVal);
-	}
-	@global(LastErrorNumber) = __mkSmallInteger(errno);
-	RETURN (nil);
+        printf("stat on '%s' for id\n", __stringVal(encodedPathName));
+# endif
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = stat((char *) __stringVal(encodedPathName), &buf);
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
+        if (ret >= 0) {
+            ino = buf.st_ino;
+            retVal = __MKUINT(ino);
+            RETURN (retVal);
+        }
+        @global(LastErrorNumber) = __mkSmallInteger(errno);
+        RETURN (nil);
     }
     RETURN (nil);
 %}.
@@ -5684,30 +5685,30 @@
 %{  /* UNLIMITEDSTACK */
 #ifdef __SCHTEAM__
     if (pathName.isStringLike()) {
-	java.io.File file = new java.io.File( pathName.asString() );
-
-	if (file.exists()) {
-	    return __c__._RETURN( new STString( file.getAbsolutePath() ));
-	}
+        java.io.File file = new java.io.File( pathName.asString() );
+
+        if (file.exists()) {
+            return __c__._RETURN( new STString( file.getAbsolutePath() ));
+        }
     }
 #else
     if (__isStringLike(pathName)) {
 # ifdef HAS_REALPATH
-	extern char *realpath();
-
-	// POSIX-2008 says, that a NULL namebuffer causes realPath to malloc()
-	// the required memory. But this does not work as of 2013-04
-	char nameBuffer[MAXPATHLEN+1];
-	char *nameP = realpath(__stringVal(pathName), nameBuffer);
-	if (nameP) {
-	    OBJ ret = __MKSTRING(nameP);
-	    // free(nameP);
-	    RETURN ( ret );
-	}
-	// fprintf(stderr, "stx[warning]: realpath(\"%s\") failed: %s\n", __stringVal(pathName), strerror(errno));
+        extern char *realpath();
+
+        // POSIX-2008 says, that a NULL namebuffer causes realPath to malloc()
+        // the required memory. But this does not work as of 2013-04
+        char nameBuffer[MAXPATHLEN+1];
+        char *nameP = realpath(__stringVal(pathName), nameBuffer);
+        if (nameP) {
+            OBJ ret = __MKSTRING(nameP);
+            // free(nameP);
+            RETURN ( ret );
+        }
+        // fprintf(stderr, "stx[warning]: realpath(\"%s\") failed: %s\n", __stringVal(pathName), strerror(errno));
 # endif /* ! HAS_REALPATH */
     } else {
-	error = @symbol(argument);     // argument is not a string
+        error = @symbol(argument);     // argument is not a string
     }
 #endif
 %}.
@@ -5718,9 +5719,9 @@
     ^ nil
 
     "
-	self primPathNameOf:'.'
-	self primPathNameOf:'/murks/quatsch/bla/.'
-	self primPathNameOf:5555
+        self primPathNameOf:'.'
+        self primPathNameOf:'/murks/quatsch/bla/.'
+        self primPathNameOf:5555
     "
 !
 
@@ -5729,7 +5730,7 @@
      For nonexistent files, nil is returned."
 
     "could be implemented as:
-	(self infoOf:aPathName) accessed
+        (self infoOf:aPathName) accessed
     "
     |osSeconds i encodedPathName|
 
@@ -5742,18 +5743,18 @@
 
     if (__isStringLike(encodedPathName)) {
 # ifdef TRACE_STAT_CALLS
-	printf("stat on '%s' for timeOfLastAccess\n", __stringVal(encodedPathName));
-# endif
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = stat((char *) __stringVal(encodedPathName), &buf);
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN (nil);
-	}
-	osSeconds = __MKUINT(buf.st_atime);
+        printf("stat on '%s' for timeOfLastAccess\n", __stringVal(encodedPathName));
+# endif
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = stat((char *) __stringVal(encodedPathName), &buf);
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN (nil);
+        }
+        osSeconds = __MKUINT(buf.st_atime);
     }
 %}.
     osSeconds notNil ifTrue:[^ Timestamp fromOSTime:(osSeconds * 1000)].
@@ -5772,7 +5773,7 @@
      For nonexistent files, nil is returned."
 
     "could be implemented as:
-	(self infoOf:aPathName) modified
+        (self infoOf:aPathName) modified
     "
 
     |osSeconds i encodedPathName|
@@ -5785,18 +5786,18 @@
 
     if (__isStringLike(encodedPathName)) {
 # ifdef TRACE_STAT_CALLS
-	printf("stat on '%s' for timeOfLastChange\n", __stringVal(encodedPathName));
-# endif
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = stat((char *) __stringVal(encodedPathName), &buf);
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( nil );
-	}
-	osSeconds = __MKUINT(buf.st_mtime);
+        printf("stat on '%s' for timeOfLastChange\n", __stringVal(encodedPathName));
+# endif
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = stat((char *) __stringVal(encodedPathName), &buf);
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( nil );
+        }
+        osSeconds = __MKUINT(buf.st_mtime);
     }
 %}.
     osSeconds notNil ifTrue:[^ Timestamp fromOSTime:(osSeconds * 1000)].
@@ -5821,7 +5822,7 @@
 
     "
      this could have been implemented as:
-	(self infoOf:aPathName) type
+        (self infoOf:aPathName) type
      but for huge directory searches the code below is faster
     "
 
@@ -5831,45 +5832,45 @@
 
     if (__isStringLike(encodedPathName)) {
 # ifdef TRACE_STAT_CALLS
-	printf("stat on '%s' for type\n", __stringVal(encodedPathName));
-# endif
-	__BEGIN_INTERRUPTABLE__
-	do {
-	    ret = stat((char *) __stringVal(encodedPathName), &buf);
-	} while (ret < 0 && errno == EINTR);
-	__END_INTERRUPTABLE__
-	if (ret < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( nil );
-	}
-	switch (buf.st_mode & S_IFMT) {
-	    case S_IFDIR:
-		RETURN ( @symbol(directory) );
-	    case S_IFREG:
-		RETURN ( @symbol(regular) );
+        printf("stat on '%s' for type\n", __stringVal(encodedPathName));
+# endif
+        __BEGIN_INTERRUPTABLE__
+        do {
+            ret = stat((char *) __stringVal(encodedPathName), &buf);
+        } while (ret < 0 && errno == EINTR);
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( nil );
+        }
+        switch (buf.st_mode & S_IFMT) {
+            case S_IFDIR:
+                RETURN ( @symbol(directory) );
+            case S_IFREG:
+                RETURN ( @symbol(regular) );
 # ifdef S_IFCHR
-	    case S_IFCHR:
-		RETURN ( @symbol(characterSpecial) );
+            case S_IFCHR:
+                RETURN ( @symbol(characterSpecial) );
 # endif
 # ifdef S_IFBLK
-	    case S_IFBLK:
-		RETURN ( @symbol(blockSpecial) );
+            case S_IFBLK:
+                RETURN ( @symbol(blockSpecial) );
 # endif
 # ifdef S_IFLNK
-	    case S_IFLNK:
-		RETURN ( @symbol(symbolicLink) );
+            case S_IFLNK:
+                RETURN ( @symbol(symbolicLink) );
 # endif
 # ifdef S_IFSOCK
-	    case S_IFSOCK:
-		RETURN ( @symbol(socket) );
+            case S_IFSOCK:
+                RETURN ( @symbol(socket) );
 # endif
 # ifdef S_IFIFO
-	    case S_IFIFO:
-		RETURN ( @symbol(fifo) );
-# endif
-	    default:
-		RETURN ( @symbol(unknown) );
-	}
+            case S_IFIFO:
+                RETURN ( @symbol(fifo) );
+# endif
+            default:
+                RETURN ( @symbol(unknown) );
+        }
     }
 %}.
     i := self infoOf:aPathName.
@@ -5911,8 +5912,8 @@
 
     if (__isSmallInteger(signalNumber)) {
 #ifdef SIG_DFL
-	signal(__intVal(signalNumber), SIG_DFL);
-	RETURN (self);
+        signal(__intVal(signalNumber), SIG_DFL);
+        RETURN (self);
 #endif
     }
 %}.
@@ -5940,22 +5941,22 @@
 
 #if (defined(F_GETFL) && defined(F_SETFL) && defined(FASYNC)) || defined(SYSV4)
     if (__isSmallInteger(fd)) {
-	f = __intVal(fd);
+        f = __intVal(fd);
 # if defined(SYSV4)
-	ret = ioctl(f, I_SETSIG, 0);
+        ret = ioctl(f, I_SETSIG, 0);
 # else /*! SYSV4*/
-	flags = fcntl(f, F_GETFL, 0);
-	/*
-	 * if already clear, there is no need for this syscall ...
-	 */
-	if (flags & FASYNC) {
-	    ret = fcntl(f, F_SETFL, flags & ~FASYNC);
-	    if (ret >= 0) ret = flags;
-	} else {
-	    ret = flags;
-	}
+        flags = fcntl(f, F_GETFL, 0);
+        /*
+         * if already clear, there is no need for this syscall ...
+         */
+        if (flags & FASYNC) {
+            ret = fcntl(f, F_SETFL, flags & ~FASYNC);
+            if (ret >= 0) ret = flags;
+        } else {
+            ret = flags;
+        }
 # endif /* !SYSV4 */
-	RETURN ( __mkSmallInteger(ret) );
+        RETURN ( __mkSmallInteger(ret) );
     }
 #endif
 %}.
@@ -5980,23 +5981,23 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     if (signalNumber.isSmallInteger()) {
-	int sigNo = signalNumber.intValue();
-
-	if (sigNo != 0) {
-	    java.lang.System.err.println("ignored disable-signal: "+sigNo);
-	}
-	return context._RETURN(self);
+        int sigNo = signalNumber.intValue();
+
+        if (sigNo != 0) {
+            java.lang.System.err.println("ignored disable-signal: "+sigNo);
+        }
+        return context._RETURN(self);
     }
 #else
     if (__isSmallInteger(signalNumber)) {
-	int sigNo = __intVal(signalNumber);
-
-	if (sigNo == 0) {
-	    RETURN (self);
-	}
+        int sigNo = __intVal(signalNumber);
+
+        if (sigNo == 0) {
+            RETURN (self);
+        }
 # ifdef SIG_IGN
-	signal(sigNo, SIG_IGN);
-	RETURN (self);
+        signal(sigNo, SIG_IGN);
+        RETURN (self);
 # endif
     }
 #endif
@@ -6018,8 +6019,8 @@
 disableTimer
     "disable timer interrupts.
      WARNING:
-	the system will not operate correctly with timer interrupts
-	disabled, because no scheduling or timeouts are possible."
+        the system will not operate correctly with timer interrupts
+        disabled, because no scheduling or timeouts are possible."
 
 %{  /* NOCONTEXT */
 
@@ -6084,73 +6085,73 @@
 # endif
 
     if (__isSmallInteger(fd)) {
-	if (firstCall) {
+        if (firstCall) {
 # ifdef HAS_SIGACTION
-	    struct sigaction act;
-
-	    /*
-	     * Do not add SA_RESTART here. A signal can cause a
-	     * thread switch, another thread can do a garbage collect
-	     * and restarted system calls may write into old
-	     * (collected) addresses.
-	     */
-
-	    act.sa_flags = SA_SIGINFO; /* <- if you add more, remember dummys at the top */
-	    sigemptyset(&act.sa_mask);
-	    act.sa_handler = __signalIoInterrupt;
-	    sigaction(THESIGNAL, &act, 0);
+            struct sigaction act;
+
+            /*
+             * Do not add SA_RESTART here. A signal can cause a
+             * thread switch, another thread can do a garbage collect
+             * and restarted system calls may write into old
+             * (collected) addresses.
+             */
+
+            act.sa_flags = SA_SIGINFO; /* <- if you add more, remember dummys at the top */
+            sigemptyset(&act.sa_mask);
+            act.sa_handler = __signalIoInterrupt;
+            sigaction(THESIGNAL, &act, 0);
 # else
 #  ifdef HAS_SIGVEC
-	    struct sigvec vec;
-
-	    vec.sv_flags = SV_INTERRUPT;
-	    sigemptyset(&vec.sv_mask);
-	    vec.sv_handler = __signalIoInterrupt;
-	    sigvec(THESIGNAL, &vec, NULL);
+            struct sigvec vec;
+
+            vec.sv_flags = SV_INTERRUPT;
+            sigemptyset(&vec.sv_mask);
+            vec.sv_handler = __signalIoInterrupt;
+            sigvec(THESIGNAL, &vec, NULL);
 #  else
-	    signal(THESIGNAL, __signalIoInterrupt);
+            signal(THESIGNAL, __signalIoInterrupt);
 #  endif /* SIGVEC */
 # endif /* SIGACTION */
-	    firstCall = 0;
-	}
+            firstCall = 0;
+        }
 #undef THESIGNAL
 
-	f = __intVal(fd);
+        f = __intVal(fd);
 # if defined(SYSV4)
-	ret = ioctl(f, I_SETSIG, S_INPUT | S_HIPRI | S_ERROR | S_RDNORM | S_RDBAND | S_MSG | S_HANGUP);
+        ret = ioctl(f, I_SETSIG, S_INPUT | S_HIPRI | S_ERROR | S_RDNORM | S_RDBAND | S_MSG | S_HANGUP);
 # else /*! SYSV4*/
-	flags = fcntl(f, F_GETFL, 0);
-	/*
-	 * if already set, there is no need for this syscall ...
-	 */
-	if (flags & FASYNC) {
-	    ret = flags;
-	} else {
-	    ret = fcntl(f, F_SETFL, flags | FASYNC);
-	    if (ret >= 0) ret = flags;
-	}
+        flags = fcntl(f, F_GETFL, 0);
+        /*
+         * if already set, there is no need for this syscall ...
+         */
+        if (flags & FASYNC) {
+            ret = flags;
+        } else {
+            ret = fcntl(f, F_SETFL, flags | FASYNC);
+            if (ret >= 0) ret = flags;
+        }
 # endif /*!SYSV4*/
 
 # if defined(F_SETOWN) || defined(FIOSETOWN)
-	{
-	    int pid;
-	    int ok;
-
-	    pid = getpid();
+        {
+            int pid;
+            int ok;
+
+            pid = getpid();
 
 #  if defined(F_SETOWN)
-	    ok = fcntl(f, F_SETOWN, pid);
-	    /* printf("F_SETOWN returns %d (%d)\n", ret, errno); */
+            ok = fcntl(f, F_SETOWN, pid);
+            /* printf("F_SETOWN returns %d (%d)\n", ret, errno); */
 #  else
-	    ok = ioctl(f, FIOSETOWN, &pid);
-	    /* printf("FIOSETOWN returns %d (%d)\n", ret, errno); */
-#  endif
-	    if (ok < 0) {
-		ret = ok;
-	    }
-	}
-# endif
-	RETURN ( __MKUINT(ret) );
+            ok = ioctl(f, FIOSETOWN, &pid);
+            /* printf("FIOSETOWN returns %d (%d)\n", ret, errno); */
+#  endif
+            if (ok < 0) {
+                ret = ok;
+            }
+        }
+# endif
+        RETURN ( __MKUINT(ret) );
     }
 #endif
 %}.
@@ -6175,12 +6176,12 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     if (signalNumber.isSmallInteger()) {
-	int sigNo = signalNumber.intValue();
-
-	if (sigNo != 0) {
-	    java.lang.System.err.println("ignored enable-signal: "+sigNo);
-	}
-	return context._RETURN(self);
+        int sigNo = signalNumber.intValue();
+
+        if (sigNo != 0) {
+            java.lang.System.err.println("ignored enable-signal: "+sigNo);
+        }
+        return context._RETURN(self);
     }
 #else
 
@@ -6270,124 +6271,124 @@
      &&  (sigNr <= SIG_LIMIT)
 # endif
     ) {
-	/*
-	 * standard signals are forced into standard handlers
-	 * - all others go into general signalInterrupt
-	 */
+        /*
+         * standard signals are forced into standard handlers
+         * - all others go into general signalInterrupt
+         */
 # if defined(SIGPOLL) && defined(SIGIO)
-	if (sigNr == SIGPOLL)
-	    sigNr = SIGIO;
-# endif
-	switch (sigNr) {
-	    case 0:
-		/* enabling a non-supported signal */
-		RETURN (self);
+        if (sigNr == SIGPOLL)
+            sigNr = SIGIO;
+# endif
+        switch (sigNr) {
+            case 0:
+                /* enabling a non-supported signal */
+                RETURN (self);
 
 # ifdef SIGBREAK
-	    case SIGBREAK:
+            case SIGBREAK:
 # endif
 # ifdef SIGINT
-	    case SIGINT:
+            case SIGINT:
 # endif
 # ifdef SIGQUIT
-	    case SIGQUIT:
+            case SIGQUIT:
 # endif
 # if defined(SIGINT) || defined(SIGQUIT) || defined(SIGBREAK)
-		handler = __signalUserInterrupt;
-		break;
+                handler = __signalUserInterrupt;
+                break;
 # endif
 # ifdef SIGFPE
-	    case SIGFPE:
-		handler = __signalFpExceptionInterrupt;
-		break;
+            case SIGFPE:
+                handler = __signalFpExceptionInterrupt;
+                break;
 # endif
 
 # ifdef SIGPIPE
-	    case SIGPIPE:
-		handler = __signalPIPEInterrupt;
-		break;
+            case SIGPIPE:
+                handler = __signalPIPEInterrupt;
+                break;
 # endif
 # ifdef SIGBUS
-	    case SIGBUS:
-		handler = __signalBUSInterrupt;
-		break;
+            case SIGBUS:
+                handler = __signalBUSInterrupt;
+                break;
 # endif
 # ifdef SIGSEGV
-	    case SIGSEGV:
-		handler = __signalSEGVInterrupt;
-		break;
+            case SIGSEGV:
+                handler = __signalSEGVInterrupt;
+                break;
 # endif
 # ifdef SIGABRT
-	    case SIGABRT:
-		handler = __signalAbortInterrupt;
-		break;
+            case SIGABRT:
+                handler = __signalAbortInterrupt;
+                break;
 # endif
 # ifdef SIGILL
-	    case SIGILL:
-		handler = __signalTrapInterrupt;
-		break;
+            case SIGILL:
+                handler = __signalTrapInterrupt;
+                break;
 # endif
 # ifdef SIGEMT
-	    case SIGEMT:
-		handler = __signalTrapInterrupt;
-		break;
+            case SIGEMT:
+                handler = __signalTrapInterrupt;
+                break;
 # endif
 # ifdef SIGIO
-	    case SIGIO:
-		handler = __signalIoInterrupt;
-		break;
+            case SIGIO:
+                handler = __signalIoInterrupt;
+                break;
 # endif
 
 # ifdef CHILD_SIGNAL
-	    case CHILD_SIGNAL:
-		handler = __signalChildInterrupt;
-		break;
+            case CHILD_SIGNAL:
+                handler = __signalChildInterrupt;
+                break;
 # endif
 # ifdef SIGALRM
-	    case SIGALRM:
-		handler = __signalTimerInterrupt;
-		break;
-# endif
-
-	    default:
-		handler = __signalInterrupt;
-		break;
-	}
-
-	{
+            case SIGALRM:
+                handler = __signalTimerInterrupt;
+                break;
+# endif
+
+            default:
+                handler = __signalInterrupt;
+                break;
+        }
+
+        {
 # ifdef HAS_SIGACTION
-	    struct sigaction act;
-
-	    /*
-	     * Do not add SA_RESTART here. A signal can cause a
-	     * thread switch, another thread can do a garbage collect
-	     * and restarted system calls may write into old
-	     * (collected) addresses.
-	     */
-
-	    act.sa_flags = SA_SIGINFO; /* <- if you add more, remember dummys at the top */
-	    sigemptyset(&act.sa_mask);
-	    act.sa_handler = handler;
-	    sigaction(sigNr, &act, 0);
+            struct sigaction act;
+
+            /*
+             * Do not add SA_RESTART here. A signal can cause a
+             * thread switch, another thread can do a garbage collect
+             * and restarted system calls may write into old
+             * (collected) addresses.
+             */
+
+            act.sa_flags = SA_SIGINFO; /* <- if you add more, remember dummys at the top */
+            sigemptyset(&act.sa_mask);
+            act.sa_handler = handler;
+            sigaction(sigNr, &act, 0);
 # else
 #  ifdef HAS_SIGVEC
-	    struct sigvec vec;
-
-	    vec.sv_flags = SV_INTERRUPT;
-	    sigemptyset(&vec.sv_mask);
-	    vec.sv_handler = handler;
-	    sigvec(sigNr, &vec, NULL);
+            struct sigvec vec;
+
+            vec.sv_flags = SV_INTERRUPT;
+            sigemptyset(&vec.sv_mask);
+            vec.sv_handler = handler;
+            sigvec(sigNr, &vec, NULL);
 #  else
-	    (void) signal(sigNr, handler);
-#  endif
-# endif
-	}
-
-	/*
-	 * maybe, we should ret the old enable-status
-	 * as boolean here ...
-	 */
-	RETURN (self);
+            (void) signal(sigNr, handler);
+#  endif
+# endif
+        }
+
+        /*
+         * maybe, we should ret the old enable-status
+         * as boolean here ...
+         */
+        RETURN (self);
     }
 #endif /* not SCHTEAM */
 %}.
@@ -6404,10 +6405,10 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     if (milliSeconds.isSmallInteger()) {
-	long millis = milliSeconds.longValue();
-
-	java.lang.System.err.println("ignored enable-timer");
-	return context._RETURN(self);
+        long millis = milliSeconds.longValue();
+
+        java.lang.System.err.println("ignored enable-timer");
+        return context._RETURN(self);
     }
 #else
     int millis;
@@ -6416,60 +6417,60 @@
 
 # ifdef SIGALRM
     {
-	static int firstCall = 1;
+        static int firstCall = 1;
 #  ifndef __signalTimerInterrupt
-	extern void __signalTimerInterrupt(SIGHANDLER_ARG);
-#  endif
-
-	if (firstCall) {
+        extern void __signalTimerInterrupt(SIGHANDLER_ARG);
+#  endif
+
+        if (firstCall) {
 #  ifdef HAS_SIGACTION
-	    struct sigaction act;
-
-	    act.sa_flags = SA_SIGINFO; /* <- if you add more, remember dummys at the top */
-	    sigemptyset(&act.sa_mask);
-	    act.sa_handler = __signalTimerInterrupt;
-	    sigaction(SIGALRM, &act, 0);
+            struct sigaction act;
+
+            act.sa_flags = SA_SIGINFO; /* <- if you add more, remember dummys at the top */
+            sigemptyset(&act.sa_mask);
+            act.sa_handler = __signalTimerInterrupt;
+            sigaction(SIGALRM, &act, 0);
 #  else
 #   ifdef HAS_SIGVEC
-	    struct sigvec vec;
-
-	    vec.sv_flags = SV_INTERRUPT;
-	    sigemptyset(&vec.sv_mask);
-	    vec.sv_handler = __signalTimerInterrupt;
-	    sigvec(SIGALRM, &vec, NULL);
+            struct sigvec vec;
+
+            vec.sv_flags = SV_INTERRUPT;
+            sigemptyset(&vec.sv_mask);
+            vec.sv_handler = __signalTimerInterrupt;
+            sigvec(SIGALRM, &vec, NULL);
 #   else /* neither SIGACTION nor SIGVEC */
-	    signal(SIGALRM, __signalTimerInterrupt);
+            signal(SIGALRM, __signalTimerInterrupt);
 #   endif /* stupid system  */
 #  endif
-	    firstCall = 0;
-	}
+            firstCall = 0;
+        }
     }
 # endif /* SIGALRM */
 
 
 # if defined(ITIMER_REAL) && !defined(NO_SETITIMER)
     {
-	struct itimerval dt;
-
-	dt.it_interval.tv_sec = 0;
-	dt.it_interval.tv_usec = 0;
-	dt.it_value.tv_sec = millis / 1000;
-	dt.it_value.tv_usec = (millis % 1000) * 1000;
-	setitimer(ITIMER_REAL, &dt, 0);
-	RETURN (true);
+        struct itimerval dt;
+
+        dt.it_interval.tv_sec = 0;
+        dt.it_interval.tv_usec = 0;
+        dt.it_value.tv_sec = millis / 1000;
+        dt.it_value.tv_usec = (millis % 1000) * 1000;
+        setitimer(ITIMER_REAL, &dt, 0);
+        RETURN (true);
     }
 # else /* no ITIMER_REAL */
 
 #  ifdef USE_SLOW_ALARM
     {
-	/*
-	 * last fallback - use alarm (which only gives 1 second resolution).
-	 * If the system does not support any of the above, you have to life
-	 * with this. The consequence is that pressing CTRL-C processing and
-	 * thread switching will take place much delayed.
-	 */
-	alarm(1);
-	RETURN(true);
+        /*
+         * last fallback - use alarm (which only gives 1 second resolution).
+         * If the system does not support any of the above, you have to life
+         * with this. The consequence is that pressing CTRL-C processing and
+         * thread switching will take place much delayed.
+         */
+        alarm(1);
+        RETURN(true);
     }
 #  endif
 # endif /* ITIMER_REAL */
@@ -6492,8 +6493,8 @@
      The process has a no chance to do some cleanup.
 
      WARNING: in order to avoid zombie processes (on unix),
-	      you may have to fetch the processes exitstatus with
-	      OperatingSystem>>getStatusOfProcess:aProcessId."
+              you may have to fetch the processes exitstatus with
+              OperatingSystem>>getStatusOfProcess:aProcessId."
 
     self sendSignal:(self sigKILL) to:processId.
 
@@ -6505,8 +6506,8 @@
      The process has a no chance to do some cleanup.
 
      WARNING: in order to avoid zombie processes (on unix),
-	      you may have to fetch the processes exitstatus with
-	      OperatingSystem>>getStatusOfProcess:aProcessId."
+              you may have to fetch the processes exitstatus with
+              OperatingSystem>>getStatusOfProcess:aProcessId."
 
     self sendSignal:(self sigKILL) to:(processGroupId negated).
 
@@ -6520,17 +6521,17 @@
      Do not confuse UNIX signals with Smalltalk-Signals.
 
      WARNING: in order to avoid zombie processes (on unix),
-	      you may have to fetch the processes exitstatus with
-	      OperatingSystem>>getStatusOfProcess:aProcessId
-	      if the signal terminates that process."
+              you may have to fetch the processes exitstatus with
+              OperatingSystem>>getStatusOfProcess:aProcessId
+              if the signal terminates that process."
 
 %{
     if (__bothSmallInteger(signalNumber, processId)) {
-	if (kill(__intVal(processId), __intVal(signalNumber)) < 0) {
-	    @global(LastErrorNumber) = __mkSmallInteger(errno);
-	    RETURN ( false );
-	}
-	RETURN ( true );
+        if (kill(__intVal(processId), __intVal(signalNumber)) < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(errno);
+            RETURN ( false );
+        }
+        RETURN ( true );
     }
 %}.
     "/
@@ -6547,7 +6548,7 @@
      On systems, where no virtual timer is available, use the real timer
      (which is of course less correct).
      OBSOLETE: the new messageTally runs as a high prio process, not using
-	       spy interrupts."
+               spy interrupts."
 
 %{  /* NOCONTEXT */
 
@@ -6586,7 +6587,7 @@
 stopSpyTimer
     "stop spy timing - disable spy timer.
      OBSOLETE: the new messageTally runs as a high prio process, not using
-	       spy interrupts."
+               spy interrupts."
 
 %{  /* NOCONTEXT */
 
@@ -6609,8 +6610,8 @@
      The process has a chance to do some cleanup.
 
      WARNING: in order to avoid zombie processes (on unix),
-	      you may have to fetch the processes exitstatus with
-	      OperatingSystem>>getStatusOfProcess:aProcessId."
+              you may have to fetch the processes exitstatus with
+              OperatingSystem>>getStatusOfProcess:aProcessId."
 
     self sendSignal:(self sigTERM) to:processId.
 
@@ -6623,8 +6624,8 @@
      The process has a chance to do some cleanup.
 
      WARNING: in order to avoid zombie processes (on unix),
-	      you may have to fetch the processes exitstatus with
-	      OperatingSystem>>getStatusOfProcess:aProcessId."
+              you may have to fetch the processes exitstatus with
+              OperatingSystem>>getStatusOfProcess:aProcessId."
 
     self sendSignal:(self sigTERM) to:(processGroupId negated).
 
@@ -6647,8 +6648,8 @@
      int fds[2];
 
      if (socketpair(AF_UNIX, SOCK_STREAM, 0, fds) == -1) {
-	@global(LastErrorNumber) = __mkSmallInteger(errno);
-	RETURN ( nil );
+        @global(LastErrorNumber) = __mkSmallInteger(errno);
+        RETURN ( nil );
      }
 
      fd1 = __mkSmallInteger(fds[0]);
@@ -6656,7 +6657,7 @@
 #endif
 %}.
     fd1 notNil ifTrue:[
-	^ Array with:fd1 with:fd2.
+        ^ Array with:fd1 with:fd2.
     ].
     ^ nil
 !
@@ -6683,18 +6684,18 @@
 
     slaveName = _getpty(&_fdM, O_RDWR|O_NDELAY, 0600, 0);
     if ((slaveName != 0) && (_fdM >= 0)) {
-	_fdS = open(slaveName, O_RDWR);
-	if (_fdS < 0) {
-	    (void)close(_fdM);
-	    _fdS = _fdM = -1;
-	}
+        _fdS = open(slaveName, O_RDWR);
+        if (_fdS < 0) {
+            (void)close(_fdM);
+            _fdS = _fdM = -1;
+        }
     } else {
-	_fdM -1;
+        _fdM -1;
     }
     if ((_fdM >= 0) && (_fdS >= 0)) {
-	fdM = __mkSmallInteger(_fdM);
-	fdS = __mkSmallInteger(_fdS);
-	ptyName = __MKSTRING(slaveName);
+        fdM = __mkSmallInteger(_fdM);
+        fdS = __mkSmallInteger(_fdS);
+        ptyName = __MKSTRING(slaveName);
     }
 #   define PTY_IS_IMPLEMENTED 1
 #endif /* IRIX5 */
@@ -6708,37 +6709,37 @@
     _fdM = open("/dev/ptmx", O_RDWR | O_NOCTTY);
 
     if (_fdM >= 0) {
-	/*
-	** grantpt() changes owner, group and mode of the pseudo-tty
-	*/
-	grantpt(_fdM);
-	unlockpt(_fdM);
-	slaveName = ptsname(_fdM);
-
-	if (slaveName != NULL) {
-	    /* printf("slave is: %s\n", slaveName); */
-	    _fdS = open(slaveName, O_RDWR);
-	    if (_fdS < 0) {
-		(void)close(_fdM);
-		_fdS = _fdM = -1;
-	    }
+        /*
+        ** grantpt() changes owner, group and mode of the pseudo-tty
+        */
+        grantpt(_fdM);
+        unlockpt(_fdM);
+        slaveName = ptsname(_fdM);
+
+        if (slaveName != NULL) {
+            /* printf("slave is: %s\n", slaveName); */
+            _fdS = open(slaveName, O_RDWR);
+            if (_fdS < 0) {
+                (void)close(_fdM);
+                _fdS = _fdM = -1;
+            }
 #if defined(UNIXWARE) || defined(solaris)
-	    else {
-		/* push terminal modules on stream */
-		ioctl(_fdS, I_PUSH, "ptem");
-		ioctl(_fdS, I_PUSH, "ldterm");
-	    }
-#endif
-	} else {
-	    (void)close(_fdM);
-	    _fdS = _fdM = -1;
-	}
+            else {
+                /* push terminal modules on stream */
+                ioctl(_fdS, I_PUSH, "ptem");
+                ioctl(_fdS, I_PUSH, "ldterm");
+            }
+#endif
+        } else {
+            (void)close(_fdM);
+            _fdS = _fdM = -1;
+        }
     }
 
     if ((_fdM >= 0) && (_fdS >= 0)) {
-	fdM = __mkSmallInteger(_fdM);
-	fdS = __mkSmallInteger(_fdS);
-	ptyName = __MKSTRING(slaveName);
+        fdM = __mkSmallInteger(_fdM);
+        fdS = __mkSmallInteger(_fdS);
+        ptyName = __MKSTRING(slaveName);
     }
 #   define PTY_IS_IMPLEMENTED 1
 #endif /* HAS_UNIX98_PTY */
@@ -6806,57 +6807,57 @@
     strncpy(line, PTY_TEMPL, sizeof(PTY_TEMPL));
 
     if (ttygid == -2) {
-	struct group *gr;
-
-	if ((gr = getgrnam("tty")) != NULL)
-	    ttygid = gr->gr_gid;
-	else
-	    ttygid = -1;
+        struct group *gr;
+
+        if ((gr = getgrnam("tty")) != NULL)
+            ttygid = gr->gr_gid;
+        else
+            ttygid = -1;
     }
 
     for (cp1 = PTY_1_CHARS; *cp1; cp1++) {
-	line[len-2] = * cp1;
-
-	for( cp2 = PTY_2_CHARS; *cp2; cp2++ ) {
-	    line[PT_INDEX] = 'p';
-	    line[len-1] = *cp2;
-
-	    if ((_fdM = open(line, O_RDWR, 0)) < 0) {
-		if (errno == ENOENT) {
-		    _fdM = _fdS = -1;
-		    goto getOutOfHere; /* out of ptys */
-		}
-	    } else {
-		line[PT_INDEX] = 't';
-
-		/*
-		 * try to set owner and mode.
-		 * this works only if running under root
-		 */
-		(void) chown( line, getuid(), ttygid );
-		(void) chmod( line, S_IRUSR | S_IWUSR | S_IWGRP );
-
-		if( (_fdS = open(line, O_RDWR, 0)) >= 0 ) {
-		    slaveName = line;
-		    goto getOutOfHere; /* success */
-		}
-		(void) close(_fdM );
-	    }
-	}
+        line[len-2] = * cp1;
+
+        for( cp2 = PTY_2_CHARS; *cp2; cp2++ ) {
+            line[PT_INDEX] = 'p';
+            line[len-1] = *cp2;
+
+            if ((_fdM = open(line, O_RDWR, 0)) < 0) {
+                if (errno == ENOENT) {
+                    _fdM = _fdS = -1;
+                    goto getOutOfHere; /* out of ptys */
+                }
+            } else {
+                line[PT_INDEX] = 't';
+
+                /*
+                 * try to set owner and mode.
+                 * this works only if running under root
+                 */
+                (void) chown( line, getuid(), ttygid );
+                (void) chmod( line, S_IRUSR | S_IWUSR | S_IWGRP );
+
+                if( (_fdS = open(line, O_RDWR, 0)) >= 0 ) {
+                    slaveName = line;
+                    goto getOutOfHere; /* success */
+                }
+                (void) close(_fdM );
+            }
+        }
     }
   getOutOfHere: ;
 
     if ((_fdM >= 0) && (_fdS >= 0)) {
-	fdM = __mkSmallInteger(_fdM);
-	fdS = __mkSmallInteger(_fdS);
-	ptyName = __MKSTRING(slaveName);
+        fdM = __mkSmallInteger(_fdM);
+        fdS = __mkSmallInteger(_fdS);
+        ptyName = __MKSTRING(slaveName);
     }
 
 #endif /* ! defined(PTY_IS_IMPLEMENTED) */
 %}.
 
     fdM notNil ifTrue:[
-	^ Array with:fdM with:fdS with:ptyName.
+        ^ Array with:fdM with:fdS with:ptyName.
     ].
 
     ^ nil
@@ -6888,15 +6889,15 @@
      int fds[2];
 
      if (pipe(fds) < 0) {
-	@global(LastErrorNumber) = __mkSmallInteger(errno);
-	RETURN ( nil );
+        @global(LastErrorNumber) = __mkSmallInteger(errno);
+        RETURN ( nil );
      }
 
      fd1 = __mkSmallInteger(fds[0]);
      fd2 = __mkSmallInteger(fds[1]);
 %}.
     fd1 notNil ifTrue:[
-	^ Array with:fd1 with:fd2.
+        ^ Array with:fd1 with:fd2.
     ].
     ^ nil
 !
@@ -6908,12 +6909,12 @@
 
     printf("setMappingMaster fd:%d\n", (int)__intVal(fd));
     if (__isSmallInteger(fd)) {
-	if (tcgetattr( __intVal(fd), &switcher) < 0) RETURN (false);
-	switcher.c_iflag = 0;
-	switcher.c_oflag = 0;
-	if (tcsetattr( __intVal(fd), TCSANOW, &switcher) >= 0) {
-	    RETURN (true);
-	}
+        if (tcgetattr( __intVal(fd), &switcher) < 0) RETURN (false);
+        switcher.c_iflag = 0;
+        switcher.c_oflag = 0;
+        if (tcsetattr( __intVal(fd), TCSANOW, &switcher) >= 0) {
+            RETURN (true);
+        }
     }
 %}.
     ^ false
@@ -6928,11 +6929,11 @@
     if (__isSmallInteger(fd)
      && __isSmallInteger(w)
      && __isSmallInteger(h)) {
-	wsize.ws_row = (unsigned short)__intVal(h);
-	wsize.ws_col = (unsigned short)__intVal(w);
-	if (ioctl(__intVal(fd), TIOCSWINSZ, (char *)&wsize) >= 0) {
-	    RETURN (true);
-	}
+        wsize.ws_row = (unsigned short)__intVal(h);
+        wsize.ws_col = (unsigned short)__intVal(w);
+        if (ioctl(__intVal(fd), TIOCSWINSZ, (char *)&wsize) >= 0) {
+            RETURN (true);
+        }
     }
 #endif
 %}.
@@ -6946,8 +6947,8 @@
 %{
 #ifndef NO_SOCKET
     if (__isSmallInteger(fileDescriptor)) {
-	shutdown(__smallIntegerVal(fileDescriptor), 1);
-	RETURN(self);
+        shutdown(__smallIntegerVal(fileDescriptor), 1);
+        RETURN(self);
     }
 #endif
 %}.
@@ -6959,36 +6960,36 @@
 closeLeftOverFiles
     "a bad bad kludge and workaround for a big bug in the linux
      getAddrInfo implementation:
-	if it gets interrupted (via a timer, for example), its domain-name
-	socket remains open and is NEVER closed.
-	These open files collect up and lead to no-more-files eventually.
+        if it gets interrupted (via a timer, for example), its domain-name
+        socket remains open and is NEVER closed.
+        These open files collect up and lead to no-more-files eventually.
      Invoking this method helps in this situation."
 
     |p|
 
     p := PipeStream
-	    readingFrom:('lsof -p ' , (OperatingSystem getProcessId printString)).
+            readingFrom:('lsof -p ' , (OperatingSystem getProcessId printString)).
 
     p linesDo:[:line |
-	|words fd|
-
-	words := line asCollectionOfWords.
-	"/ COMMAND PID USER   FD   TYPE     DEVICE    SIZE    NODE NAME
-	words first = 'stx' ifTrue:[
-	    words second = (OperatingSystem getProcessId printString) ifTrue:[
-		(words fourth endsWith:'u') ifTrue:[
-		    (words fifth = 'IPv4') ifTrue:[
-			(words seventh = 'UDP') ifTrue:[
-			    (words last endsWith:'domain') ifTrue:[
-				fd := Number readFrom:(words fourth copyButLast).
+        |words fd|
+
+        words := line asCollectionOfWords.
+        "/ COMMAND PID USER   FD   TYPE     DEVICE    SIZE    NODE NAME
+        words first = 'stx' ifTrue:[
+            words second = (OperatingSystem getProcessId printString) ifTrue:[
+                (words fourth endsWith:'u') ifTrue:[
+                    (words fifth = 'IPv4') ifTrue:[
+                        (words seventh = 'UDP') ifTrue:[
+                            (words last endsWith:'domain') ifTrue:[
+                                fd := Number readFrom:(words fourth copyButLast).
 Transcript showCR:line.
-				OperatingSystem closeFd:fd.
-			    ]
-			]
-		    ]
-		]
-	    ]
-	]
+                                OperatingSystem closeFd:fd.
+                            ]
+                        ]
+                    ]
+                ]
+            ]
+        ]
     ].
     p close.
 
@@ -7005,10 +7006,10 @@
     int dupFd;
 
     if (__isSmallInteger(aFileDescriptor)) {
-	dupFd = dup(__smallIntegerVal(aFileDescriptor));
-	if (dupFd >= 0) {
-	    RETURN(__mkSmallInteger(dupFd));
-	}
+        dupFd = dup(__smallIntegerVal(aFileDescriptor));
+        if (dupFd >= 0) {
+            RETURN(__mkSmallInteger(dupFd));
+        }
     }
 %}.
     ^ self primitiveFailed.
@@ -7063,49 +7064,49 @@
 getDomainName
     "return the domain this host is in.
      Notice:
-	not all systems support this; on some, #unknown is returned."
+        not all systems support this; on some, #unknown is returned."
 
     |domainName idx hostName primDomainName|
 
     "/ use cached value, if present
     (DomainName notNil and:[DomainName ~~ #unknown]) ifTrue:[
-	^ DomainName
+        ^ DomainName
     ].
 
     primDomainName := domainName := self primGetDomainName.
     domainName = '(none)' ifTrue:[
-	domainName := nil.
+        domainName := nil.
     ].
     domainName isEmptyOrNil ifTrue:[
-	"sometimes, we can extract the domainName from the hostName ..."
-	hostName := self primGetHostName.
-	hostName notNil ifTrue:[
-	    idx := hostName indexOf:$..
-	    idx ~~ 0 ifTrue:[
-		domainName := hostName copyFrom:idx+1.
-	    ]
-	].
-	domainName isEmptyOrNil ifTrue:[
-	    "/ fallBack
-	    domainName := self getEnvironment:'DOMAIN'.
-
-	    "if #primGetDomainName did work, /bin/domainname would return the same result"
-	    (domainName isNil and:[primDomainName isNil]) ifTrue:[
-		domainName := self getCommandOutputFrom:'/bin/domainname'.
-		(domainName isEmptyOrNil or:[ domainName = '(none)' ]) ifTrue:[
-		    domainName := nil.
-		].
-	    ].
-	    domainName isNil ifTrue:[
-		DomainName ~~ #unknown ifTrue:[
-		    "/ only warn once - the warning can be ignored, if you do not use the domain name
-		    ObjectMemory debugPrinting ifTrue:[
-			'UnixOperatingSystem [info]: cannot find out domainname' infoPrintCR.
-		    ].
-		].
-		domainName := #unknown.
-	    ].
-	].
+        "sometimes, we can extract the domainName from the hostName ..."
+        hostName := self primGetHostName.
+        hostName notNil ifTrue:[
+            idx := hostName indexOf:$..
+            idx ~~ 0 ifTrue:[
+                domainName := hostName copyFrom:idx+1.
+            ]
+        ].
+        domainName isEmptyOrNil ifTrue:[
+            "/ fallBack
+            domainName := self getEnvironment:'DOMAIN'.
+
+            "if #primGetDomainName did work, /bin/domainname would return the same result"
+            (domainName isNil and:[primDomainName isNil]) ifTrue:[
+                domainName := self getCommandOutputFrom:'/bin/domainname'.
+                (domainName isEmptyOrNil or:[ domainName = '(none)' ]) ifTrue:[
+                    domainName := nil.
+                ].
+            ].
+            domainName isNil ifTrue:[
+                DomainName ~~ #unknown ifTrue:[
+                    "/ only warn once - the warning can be ignored, if you do not use the domain name
+                    ObjectMemory debugPrinting ifTrue:[
+                        'UnixOperatingSystem [info]: cannot find out domainname' infoPrintCR.
+                    ].
+                ].
+                domainName := #unknown.
+            ].
+        ].
     ].
 
     "cache, because domainName fetching may be expensive;
@@ -7141,9 +7142,9 @@
      * get the size of the environment
      */
     if (environ) {
-	for (env = environ; *env; env++) {
-	    nEnv++;
-	}
+        for (env = environ; *env; env++) {
+            nEnv++;
+        }
     }
 
     /*
@@ -7151,49 +7152,49 @@
      */
     resultArray = __ARRAY_NEW_INT(nEnv * 2);
     if (resultArray == nil) {
-	error = @symbol(allocationFailure);
-	goto bad;
+        error = @symbol(allocationFailure);
+        goto bad;
     }
 
     if (environ) {
-	int envIndex;
-
-	for (env = environ, envIndex = 0; *env; env++) {
-	    OBJ t;
-	    char *separatorPtr;
-
-	    separatorPtr = strchr(*env, '=');
-	    t = __MKSTRING_L(*env, separatorPtr-*env);
-	    __arrayVal(resultArray)[envIndex++] = t;
-	    __STORE(resultArray, t);
-	    if (separatorPtr == 0) {
-		t = nil;
-	    } else {
-		t = __MKSTRING(separatorPtr+1);
-	    }
-	    __arrayVal(resultArray)[envIndex++] = t;
-	    __STORE(resultArray, t);
-	}
+        int envIndex;
+
+        for (env = environ, envIndex = 0; *env; env++) {
+            OBJ t;
+            char *separatorPtr;
+
+            separatorPtr = strchr(*env, '=');
+            t = __MKSTRING_L(*env, separatorPtr-*env);
+            __arrayVal(resultArray)[envIndex++] = t;
+            __STORE(resultArray, t);
+            if (separatorPtr == 0) {
+                t = nil;
+            } else {
+                t = __MKSTRING(separatorPtr+1);
+            }
+            __arrayVal(resultArray)[envIndex++] = t;
+            __STORE(resultArray, t);
+        }
     }
 
 bad:;
 %}.
     error notNil ifTrue:[
-	^ self primitiveFailed:error.
+        ^ self primitiveFailed:error.
     ].
 
     sz := resultArray size.
     dict := Dictionary new:(sz // 2).
     1 to:sz by:2 do:[:i |
-	|key|
-
-	key := resultArray at:i.
-	key notNil ifTrue:[
-	    "same behavior as getenv() - the first entry takes precedence"
-	    (dict includesKey:key) ifFalse:[
-		dict at:key put:(resultArray at:i+1)
-	    ].
-	].
+        |key|
+
+        key := resultArray at:i.
+        key notNil ifTrue:[
+            "same behavior as getenv() - the first entry takes precedence"
+            (dict includesKey:key) ifFalse:[
+                dict at:key put:(resultArray at:i+1)
+            ].
+        ].
     ].
     ^ dict
 
@@ -7208,26 +7209,26 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     {
-	java.lang.String val = java.lang.System.getenv( aStringOrSymbol.asString() );
-	STObject retVal;
-
-	if (val == null) {
-	    retVal = STObject.Nil;
-	} else {
-	    retVal = new STString( val );
-	}
-	return context._RETURN( retVal );
-	/* NOTREACHED */
+        java.lang.String val = java.lang.System.getenv( aStringOrSymbol.asString() );
+        STObject retVal;
+
+        if (val == null) {
+            retVal = STObject.Nil;
+        } else {
+            retVal = new STString( val );
+        }
+        return context._RETURN( retVal );
+        /* NOTREACHED */
     }
 #else
     extern char *getenv();
 
     if (__isStringLike(aStringOrSymbol)) {
-	char *env =  getenv(__stringVal(aStringOrSymbol));
-	if (env) {
-	    RETURN ( __MKSTRING(env) );
-	}
-	RETURN ( nil );
+        char *env =  getenv(__stringVal(aStringOrSymbol));
+        if (env) {
+            RETURN ( __MKSTRING(env) );
+        }
+        RETURN ( nil );
     }
 #endif /* not SCHTEAM */
 %}.
@@ -7250,22 +7251,22 @@
     |hostName|
 
     (HostName notNil and:[HostName ~~ #unknown]) ifTrue:[
-	^ HostName
+        ^ HostName
     ].
 
     hostName := self primGetHostName.
     hostName isNil ifTrue:[
-	"fallBack - in non-antique systes we never come here"
-	hostName := self getEnvironment:'HOST'.
-	hostName isNil ifTrue:[
-	    hostName := self getCommandOutputFrom:'/bin/hostname'
-	].
-	hostName isNil ifTrue:[
-	    HostName ~~ #unknown ifTrue:[
-		'UnixOperatingSystem [info]: cannot find out hostname' infoPrintCR.
-		hostName := #unknown.
-	    ].
-	].
+        "fallBack - in non-antique systes we never come here"
+        hostName := self getEnvironment:'HOST'.
+        hostName isNil ifTrue:[
+            hostName := self getCommandOutputFrom:'/bin/hostname'
+        ].
+        hostName isNil ifTrue:[
+            HostName ~~ #unknown ifTrue:[
+                'UnixOperatingSystem [info]: cannot find out hostname' infoPrintCR.
+                hostName := #unknown.
+            ].
+        ].
     ].
 
     "cache, because hostname fetching may be expensive;
@@ -7283,42 +7284,42 @@
     "return a dictionary filled with values from the locale information;
      Not all fields may be present, depending on the OS's setup and capabilities.
      Possible fields are:
-	decimalPoint                    <String>
-
-	thousandsSep                    <String>
-
-	internationalCurrencySymbol     <String>
-
-	currencySymbol                  <String>
-
-	monetaryDecimalPoint            <String>
-
-	monetaryThousandsSeparator      <String>
-
-	positiveSign                    <String>
-
-	negativeSign                    <String>
-
-	internationalFractionalDigits   <Integer>
-
-	fractionalDigits                <Integer>
-
-	positiveSignPrecedesCurrencySymbol      <Boolean>
-
-	negativeSignPrecedesCurrencySymbol      <Boolean>
-
-	positiveSignSeparatedBySpaceFromCurrencySymbol  <Boolean>
-
-	negativeSignSeparatedBySpaceFromCurrencySymbol  <Boolean>
-
-	positiveSignPosition                            <Symbol>
-							one of: #parenthesesAround,
-								#signPrecedes,
-								#signSuceeds,
-								#signPrecedesCurrencySymbol,
-								#signSuceedsCurrencySymbol
-
-	negativeSignPosition                            <like above>
+        decimalPoint                    <String>
+
+        thousandsSep                    <String>
+
+        internationalCurrencySymbol     <String>
+
+        currencySymbol                  <String>
+
+        monetaryDecimalPoint            <String>
+
+        monetaryThousandsSeparator      <String>
+
+        positiveSign                    <String>
+
+        negativeSign                    <String>
+
+        internationalFractionalDigits   <Integer>
+
+        fractionalDigits                <Integer>
+
+        positiveSignPrecedesCurrencySymbol      <Boolean>
+
+        negativeSignPrecedesCurrencySymbol      <Boolean>
+
+        positiveSignSeparatedBySpaceFromCurrencySymbol  <Boolean>
+
+        negativeSignSeparatedBySpaceFromCurrencySymbol  <Boolean>
+
+        positiveSignPosition                            <Symbol>
+                                                        one of: #parenthesesAround,
+                                                                #signPrecedes,
+                                                                #signSuceeds,
+                                                                #signPrecedesCurrencySymbol,
+                                                                #signSuceedsCurrencySymbol
+
+        negativeSignPosition                            <like above>
 
      it is up to the application to deal with undefined values.
 
@@ -7329,9 +7330,9 @@
     |info val|
 
     LocaleInfo notNil ifTrue:[
-	"/ return the internal info; useful on systems which do not
-	"/ support this.
-	^ LocaleInfo
+        "/ return the internal info; useful on systems which do not
+        "/ support this.
+        ^ LocaleInfo
     ].
 
     info := IdentityDictionary new.
@@ -7352,31 +7353,31 @@
     int   csNegSepBySpace;      /* money: 1 if currency symbol should be separated by a space from a negative value; 0 if no space */
     int   csPosSignPosition;    /* money: 0: ()'s around the value & currency symbol */
     int   csNegSignPosition;    /*        1: sign precedes the value & currency symbol */
-				/*        2: sign succeeds the value & currency symbol */
-				/*        3: sign immediately precedes the currency symbol */
-				/*        4: sign immediately suceeds the currency symbol */
+                                /*        2: sign succeeds the value & currency symbol */
+                                /*        3: sign immediately precedes the currency symbol */
+                                /*        4: sign immediately suceeds the currency symbol */
 
 #if defined(HAS_LOCALECONV)
     struct lconv *conf;
 
     conf = localeconv();
     if (conf) {
-	decimalPoint = conf->decimal_point;
-	thousandsSep = conf->thousands_sep;
-	intCurrencySymbol = conf->int_curr_symbol;
-	currencySymbol = conf->currency_symbol;
-	monDecimalPoint = conf->mon_decimal_point;
-	monThousandsSep = conf->mon_thousands_sep;
-	positiveSign = conf->positive_sign;
-	negativeSign = conf->negative_sign;
-	intFractDigits = conf->int_frac_digits;
-	fractDigits = conf->frac_digits;
-	csPosPrecedes = conf->p_cs_precedes;
-	csNegPrecedes = conf->n_cs_precedes;
-	csPosSepBySpace = conf->p_sep_by_space;
-	csNegSepBySpace = conf->n_sep_by_space;
-	csPosSignPosition = conf->p_sign_posn;
-	csNegSignPosition = conf->n_sign_posn;
+        decimalPoint = conf->decimal_point;
+        thousandsSep = conf->thousands_sep;
+        intCurrencySymbol = conf->int_curr_symbol;
+        currencySymbol = conf->currency_symbol;
+        monDecimalPoint = conf->mon_decimal_point;
+        monThousandsSep = conf->mon_thousands_sep;
+        positiveSign = conf->positive_sign;
+        negativeSign = conf->negative_sign;
+        intFractDigits = conf->int_frac_digits;
+        fractDigits = conf->frac_digits;
+        csPosPrecedes = conf->p_cs_precedes;
+        csNegPrecedes = conf->n_cs_precedes;
+        csPosSepBySpace = conf->p_sep_by_space;
+        csNegSepBySpace = conf->n_sep_by_space;
+        csPosSignPosition = conf->p_sign_posn;
+        csNegSignPosition = conf->n_sign_posn;
     }
 #else
     decimalPoint = (char *)0;
@@ -7397,129 +7398,129 @@
     csNegSignPosition = -1;
 #endif
     if (decimalPoint) {
-	val = __MKSTRING(decimalPoint);
-	__AT_PUT_(info, @symbol(decimalPoint), val);
+        val = __MKSTRING(decimalPoint);
+        __AT_PUT_(info, @symbol(decimalPoint), val);
     }
     if (thousandsSep) {
-	val = __MKSTRING(thousandsSep);
-	__AT_PUT_(info, @symbol(thousandsSeparator), val);
+        val = __MKSTRING(thousandsSep);
+        __AT_PUT_(info, @symbol(thousandsSeparator), val);
     }
     if (intCurrencySymbol) {
-	val = __MKSTRING(intCurrencySymbol);
-	__AT_PUT_(info, @symbol(internationCurrencySymbol), val);
+        val = __MKSTRING(intCurrencySymbol);
+        __AT_PUT_(info, @symbol(internationCurrencySymbol), val);
     }
     if (currencySymbol) {
-	val = __MKSTRING(currencySymbol);
-	__AT_PUT_(info, @symbol(currencySymbol), val);
+        val = __MKSTRING(currencySymbol);
+        __AT_PUT_(info, @symbol(currencySymbol), val);
     }
     if (monDecimalPoint) {
-	val = __MKSTRING(monDecimalPoint);
-	__AT_PUT_(info, @symbol(monetaryDecimalPoint), val);
+        val = __MKSTRING(monDecimalPoint);
+        __AT_PUT_(info, @symbol(monetaryDecimalPoint), val);
     }
     if (monThousandsSep) {
-	val = __MKSTRING(monThousandsSep);
-	__AT_PUT_(info, @symbol(monetaryThousandsSeparator), val);
+        val = __MKSTRING(monThousandsSep);
+        __AT_PUT_(info, @symbol(monetaryThousandsSeparator), val);
     }
     if (positiveSign) {
-	val = __MKSTRING(positiveSign);
-	__AT_PUT_(info, @symbol(positiveSign), val);
+        val = __MKSTRING(positiveSign);
+        __AT_PUT_(info, @symbol(positiveSign), val);
     }
     if (negativeSign) {
-	val = __MKSTRING(negativeSign);
-	__AT_PUT_(info, @symbol(negativeSign), val);
+        val = __MKSTRING(negativeSign);
+        __AT_PUT_(info, @symbol(negativeSign), val);
     }
     if (intFractDigits >= 0) {
-	__AT_PUT_(info, @symbol(internationalFractionalDigits),  __mkSmallInteger(intFractDigits));
+        __AT_PUT_(info, @symbol(internationalFractionalDigits),  __mkSmallInteger(intFractDigits));
     }
     if (fractDigits >= 0) {
-	__AT_PUT_(info, @symbol(fractionalDigits),  __mkSmallInteger(fractDigits));
+        __AT_PUT_(info, @symbol(fractionalDigits),  __mkSmallInteger(fractDigits));
     }
     if (csPosPrecedes >= 0) {
-	if (csPosPrecedes == 0) {
-	    val = false;
-	} else {
-	    val = true;
-	}
-	__AT_PUT_(info, @symbol(positiveSignPrecedesCurrencySymbol), val );
+        if (csPosPrecedes == 0) {
+            val = false;
+        } else {
+            val = true;
+        }
+        __AT_PUT_(info, @symbol(positiveSignPrecedesCurrencySymbol), val );
     }
     if (csNegPrecedes >= 0) {
-	if (csNegPrecedes == 0) {
-	    val = false;
-	} else {
-	    val = true;
-	}
-	__AT_PUT_(info, @symbol(negativeSignPrecedesCurrencySymbol), val );
+        if (csNegPrecedes == 0) {
+            val = false;
+        } else {
+            val = true;
+        }
+        __AT_PUT_(info, @symbol(negativeSignPrecedesCurrencySymbol), val );
     }
     if (csPosSepBySpace >= 0) {
-	if (csPosSepBySpace == 0) {
-	    val = false;
-	} else {
-	    val = true;
-	}
-	__AT_PUT_(info, @symbol(positiveSignSeparatedBySpaceFromCurrencySymbol), val);
+        if (csPosSepBySpace == 0) {
+            val = false;
+        } else {
+            val = true;
+        }
+        __AT_PUT_(info, @symbol(positiveSignSeparatedBySpaceFromCurrencySymbol), val);
     }
     if (csNegSepBySpace >= 0) {
-	if (csNegSepBySpace == 0) {
-	    val = false;
-	} else {
-	    val = true;
-	}
-	__AT_PUT_(info, @symbol(negativeSignSeparatedBySpaceFromCurrencySymbol), val);
+        if (csNegSepBySpace == 0) {
+            val = false;
+        } else {
+            val = true;
+        }
+        __AT_PUT_(info, @symbol(negativeSignSeparatedBySpaceFromCurrencySymbol), val);
     }
     switch (csPosSignPosition) {
-	case 0:
-	    val = @symbol(parenthesesAround);
-	    break;
-
-	case 1:
-	    val = @symbol(signPrecedes);
-	    break;
-
-	case 2:
-	    val = @symbol(signSuceeds);
-	    break;
-
-	case 3:
-	    val = @symbol(signPrecedesCurrencySymbol);
-	    break;
-
-	case 4:
-	    val = @symbol(signSuceedsCurrencySymbol);
-	    break;
-
-	default:
-	    val = nil;
+        case 0:
+            val = @symbol(parenthesesAround);
+            break;
+
+        case 1:
+            val = @symbol(signPrecedes);
+            break;
+
+        case 2:
+            val = @symbol(signSuceeds);
+            break;
+
+        case 3:
+            val = @symbol(signPrecedesCurrencySymbol);
+            break;
+
+        case 4:
+            val = @symbol(signSuceedsCurrencySymbol);
+            break;
+
+        default:
+            val = nil;
     }
     if (val != nil) {
-	__AT_PUT_(info, @symbol(positiveSignPosition), val);
+        __AT_PUT_(info, @symbol(positiveSignPosition), val);
     }
 
     switch (csNegSignPosition) {
-	case 0:
-	    val = @symbol(parenthesesAround);
-	    break;
-
-	case 1:
-	    val = @symbol(signPrecedes);
-	    break;
-
-	case 2:
-	    val = @symbol(signSuceeds);
-	    break;
-
-	case 3:
-	    val = @symbol(signPrecedesCurrencySymbol);
-	    break;
-
-	case 4:
-	    val = @symbol(signSuceedsCurrencySymbol);
-	    break;
-
-	default:
-	    val = nil;
+        case 0:
+            val = @symbol(parenthesesAround);
+            break;
+
+        case 1:
+            val = @symbol(signPrecedes);
+            break;
+
+        case 2:
+            val = @symbol(signSuceeds);
+            break;
+
+        case 3:
+            val = @symbol(signPrecedesCurrencySymbol);
+            break;
+
+        case 4:
+            val = @symbol(signSuceedsCurrencySymbol);
+            break;
+
+        default:
+            val = nil;
     }
     if (val != nil) {
-	__AT_PUT_(info, @symbol(negativeSignPosition), val);
+        __AT_PUT_(info, @symbol(negativeSignPosition), val);
     }
 %}.
     ^ info
@@ -7533,15 +7534,15 @@
 
 getNetworkAddressInfo
     "return a Dictionary of network interface information.
-	key -> name of interface
-	value -> a Set of network address
-		information for the interface - a dictionaries containing the
-		information about the configuration of each interface in the system.
-		The dictionary keys are:
-		    #address
-		    #netmask
-		    #flags
-		    #destAddress"
+        key -> name of interface
+        value -> a Set of network address
+                information for the interface - a dictionaries containing the
+                information about the configuration of each interface in the system.
+                The dictionary keys are:
+                    #address
+                    #netmask
+                    #flags
+                    #destAddress"
 
     |returnArray addressArray nameArray noOfIf retDictionary error retIndex|
 
@@ -7561,8 +7562,8 @@
     OBJ t;
 
     if (getifaddrs(&ifap) < 0) {
-	error = __MKSTRING("getifaddrs() failed");
-	goto out;
+        error = __MKSTRING("getifaddrs() failed");
+        goto out;
     }
 
     for (ifaLoop = ifap; ifaLoop != 0; ifaLoop = ifaLoop->ifa_next) n_ifa++;
@@ -7570,49 +7571,49 @@
     returnArray = __ARRAY_NEW_INT(n_ifa*5);
 
     if (returnArray == nil) {
-	/* Creating a string wouldn't work here */
-	error = @symbol(allocationFailure);
-	goto bad;
+        /* Creating a string wouldn't work here */
+        error = @symbol(allocationFailure);
+        goto bad;
     }
 
     for (ifaLoop = ifap; ifaLoop != 0; ifaLoop = ifaLoop->ifa_next) {
-	int family, len;
-
-	if (ifaLoop->ifa_addr == 0)
-	       continue;
-	family = ifaLoop->ifa_addr->sa_family;
-	switch (family) {
-	case AF_INET:
-	    len = sizeof(struct sockaddr_in);
-	    break;
-	case AF_INET6:
-	    len = sizeof(struct sockaddr_in6);
-	    break;
+        int family, len;
+
+        if (ifaLoop->ifa_addr == 0)
+               continue;
+        family = ifaLoop->ifa_addr->sa_family;
+        switch (family) {
+        case AF_INET:
+            len = sizeof(struct sockaddr_in);
+            break;
+        case AF_INET6:
+            len = sizeof(struct sockaddr_in6);
+            break;
 #if 0
-	case AF_PACKET:
-	    len = sizeof(sockaddr_ll);
-	    break;
-#endif
-	default:
-	    /* skip */
-	    continue;
-	};
-	t = __MKSTRING(ifaLoop->ifa_name);
-	__arrayVal(returnArray)[retI++] = t; __STORE(returnArray, t);
-	t = __MKUINT(ifaLoop->ifa_flags);
-	__arrayVal(returnArray)[retI++] = t; __STORE(returnArray, t);
-	t = __MKBYTEARRAY((char *)ifaLoop->ifa_addr, len);
-	__arrayVal(returnArray)[retI++] = t; __STORE(returnArray, t);
-	if (ifaLoop->ifa_netmask != 0) {
-	    t = __MKBYTEARRAY((char *)ifaLoop->ifa_netmask, len);
-	    __arrayVal(returnArray)[retI] = t; __STORE(returnArray, t);
-	}
-	retI++;
-	if (ifaLoop->ifa_dstaddr != 0) {
-	    t = __MKBYTEARRAY((char *)ifaLoop->ifa_dstaddr, len);
-	    __arrayVal(returnArray)[retI] = t; __STORE(returnArray, t);
-	}
-	retI++;
+        case AF_PACKET:
+            len = sizeof(sockaddr_ll);
+            break;
+#endif
+        default:
+            /* skip */
+            continue;
+        };
+        t = __MKSTRING(ifaLoop->ifa_name);
+        __arrayVal(returnArray)[retI++] = t; __STORE(returnArray, t);
+        t = __MKUINT(ifaLoop->ifa_flags);
+        __arrayVal(returnArray)[retI++] = t; __STORE(returnArray, t);
+        t = __MKBYTEARRAY((char *)ifaLoop->ifa_addr, len);
+        __arrayVal(returnArray)[retI++] = t; __STORE(returnArray, t);
+        if (ifaLoop->ifa_netmask != 0) {
+            t = __MKBYTEARRAY((char *)ifaLoop->ifa_netmask, len);
+            __arrayVal(returnArray)[retI] = t; __STORE(returnArray, t);
+        }
+        retI++;
+        if (ifaLoop->ifa_dstaddr != 0) {
+            t = __MKBYTEARRAY((char *)ifaLoop->ifa_dstaddr, len);
+            __arrayVal(returnArray)[retI] = t; __STORE(returnArray, t);
+        }
+        retI++;
     }
 
     noOfIf = __mkSmallInteger(n_ifa);
@@ -7637,7 +7638,7 @@
 
     afinet_socket = socket(AF_INET, SOCK_DGRAM, 0);
     if (afinet_socket < 0) {
-	goto bad;
+        goto bad;
     }
 
     /*
@@ -7648,9 +7649,9 @@
     ifc.ifc_buf = (caddr_t) buf;
 
     if (ioctl (afinet_socket, SIOCGIFCONF, (caddr_t) &ifc) < 0) {
-	close(afinet_socket);
-	error = __MKSTRING("ioctl(SIOCGIFCONF) failed");
-	goto bad;
+        close(afinet_socket);
+        error = __MKSTRING("ioctl(SIOCGIFCONF) failed");
+        goto bad;
     }
 
     n_ifs = ifc.ifc_len / sizeof (struct ifreq);
@@ -7659,9 +7660,9 @@
     addressArray = __ARRAY_NEW_INT(n_ifs);
 
     if (nameArray == nil || addressArray == nil) {
-	/* Creating a string wouldn/t work here */
-	error = @symbol(allocationFailure);
-	goto bad;
+        /* Creating a string wouldn/t work here */
+        error = @symbol(allocationFailure);
+        goto bad;
     }
 
     /*
@@ -7671,29 +7672,29 @@
     countOfIf = 0;
 
     for (i=0, ifr = ifc.ifc_req; i < n_ifs; i++, ifr++) {
-	/*
-	** Get address for this interface
-	*/
-	memset (&ifreq, 0, sizeof(ifreq));
-	memcpy (ifreq.ifr_name, ifr->ifr_name, sizeof(ifr->ifr_name));
-	if (ioctl (afinet_socket, SIOCGIFADDR, &ifreq) >= 0) {
-	    t = __MKBYTEARRAY((char *)&ifreq.ifr_addr, sizeof(ifreq.ifr_addr));
-	    __arrayVal(addressArray)[countOfIf] = t; __STORE(addressArray, t);
-	    t = __MKSTRING(&ifreq.ifr_name);
-	    __arrayVal(nameArray)[countOfIf] = t; __STORE(nameArray, t);
-	    countOfIf++;
-	} else {
-	    if (@global(InfoPrinting) == true) {
-		fprintf(stderr, "OS [warning]: SIOCGIFADDR failed: %d\n", errno);
-	    }
-	}
-	error = __MKSTRING("ioctl(SIOCGIFCONF) failed");
+        /*
+        ** Get address for this interface
+        */
+        memset (&ifreq, 0, sizeof(ifreq));
+        memcpy (ifreq.ifr_name, ifr->ifr_name, sizeof(ifr->ifr_name));
+        if (ioctl (afinet_socket, SIOCGIFADDR, &ifreq) >= 0) {
+            t = __MKBYTEARRAY((char *)&ifreq.ifr_addr, sizeof(ifreq.ifr_addr));
+            __arrayVal(addressArray)[countOfIf] = t; __STORE(addressArray, t);
+            t = __MKSTRING(&ifreq.ifr_name);
+            __arrayVal(nameArray)[countOfIf] = t; __STORE(nameArray, t);
+            countOfIf++;
+        } else {
+            if (@global(InfoPrinting) == true) {
+                fprintf(stderr, "OS [warning]: SIOCGIFADDR failed: %d\n", errno);
+            }
+        }
+        error = __MKSTRING("ioctl(SIOCGIFCONF) failed");
     }
 
     noOfIf = __mkSmallInteger(countOfIf);
 bad:
     if (afinet_socket >= 0)
-	close(afinet_socket);
+        close(afinet_socket);
 #else
     error = @symbol(notSupported);
 #endif /* defined(SIOCGIFADDR) */
@@ -7702,35 +7703,35 @@
 
     retDictionary := Dictionary new:noOfIf.
     error notNil ifTrue:[
-	self primitiveFailed:error.
-	"return empty dictionary if proceeding from error"
-	^  retDictionary.
+        self primitiveFailed:error.
+        "return empty dictionary if proceeding from error"
+        ^  retDictionary.
     ].
 
     retIndex := 1.
 
     1 to:noOfIf do:[:cnt|
-	|name addressBytes set dict|
-
-	name := returnArray at:retIndex.
-	addressBytes := returnArray at:retIndex+2.
-
-	addressBytes notNil ifTrue:[
-	    set := retDictionary at:name ifAbsentPut:[Set new].
-	    dict := Dictionary new:5.
-	    dict at:#flags put:(returnArray at:retIndex+1).
-	    dict at:#address put:(SocketAddress fromBytes:addressBytes).
-	    addressBytes := returnArray at:retIndex+3.
-	    addressBytes notNil ifTrue:[
-		dict at:#netMask put:(SocketAddress fromBytes:addressBytes).
-	    ].
-	    addressBytes := returnArray at:retIndex+4.
-	    addressBytes notNil ifTrue:[
-		dict at:#destAddress put:(SocketAddress fromBytes:addressBytes).
-	    ].
-	    set add:dict.
-	].
-	retIndex := retIndex + 5.
+        |name addressBytes set dict|
+
+        name := returnArray at:retIndex.
+        addressBytes := returnArray at:retIndex+2.
+
+        addressBytes notNil ifTrue:[
+            set := retDictionary at:name ifAbsentPut:[Set new].
+            dict := Dictionary new:5.
+            dict at:#flags put:(returnArray at:retIndex+1).
+            dict at:#address put:(SocketAddress fromBytes:addressBytes).
+            addressBytes := returnArray at:retIndex+3.
+            addressBytes notNil ifTrue:[
+                dict at:#netMask put:(SocketAddress fromBytes:addressBytes).
+            ].
+            addressBytes := returnArray at:retIndex+4.
+            addressBytes notNil ifTrue:[
+                dict at:#destAddress put:(SocketAddress fromBytes:addressBytes).
+            ].
+            set add:dict.
+        ].
+        retIndex := retIndex + 5.
     ].
 
     ^ retDictionary
@@ -7742,8 +7743,8 @@
 
 getNetworkAddresses
     "return a dictionary filled with
-	key -> name of interface
-	value -> the socket adress of the interface
+        key -> name of interface
+        value -> the socket adress of the interface
      for each interface"
 
     |addressArray nameArray noOfIf retDictionary error|
@@ -7767,8 +7768,8 @@
 
     afinet_socket = socket(AF_INET, SOCK_DGRAM, 0);
     if (afinet_socket < 0) {
-	error = __MKSTRING("Cannot open socket");
-	goto bad;
+        error = __MKSTRING("Cannot open socket");
+        goto bad;
     }
 
     /*
@@ -7779,9 +7780,9 @@
     ifc.ifc_buf = (caddr_t) buf;
 
     if (ioctl (afinet_socket, SIOCGIFCONF, (caddr_t) &ifc) < 0) {
-	close(afinet_socket);
-	error = __MKSTRING("ioctl(SIOCGIFCONF) failed");
-	goto bad;
+        close(afinet_socket);
+        error = __MKSTRING("ioctl(SIOCGIFCONF) failed");
+        goto bad;
     }
 
     // get the number of interfaces in the returned structure
@@ -7797,19 +7798,19 @@
     n_ifs = ifc.ifc_len / sizeof (struct ifreq);
 #else
     {
-	unsigned char *cp = buf;
-	char *limit = buf + ifc.ifc_len;
-
-	n_ifs = 0;
-	while (cp < limit) {
-	    int sz;
-
-	    ifr = (struct ifreq *)cp;
-	    sz = IFNAMSIZ + ifr->ifr_addr.sa_len;
-
-	    cp += sz;
-	    n_ifs++;
-	}
+        unsigned char *cp = buf;
+        char *limit = buf + ifc.ifc_len;
+
+        n_ifs = 0;
+        while (cp < limit) {
+            int sz;
+
+            ifr = (struct ifreq *)cp;
+            sz = IFNAMSIZ + ifr->ifr_addr.sa_len;
+
+            cp += sz;
+            n_ifs++;
+        }
     }
 #endif
 
@@ -7817,9 +7818,9 @@
     addressArray = __ARRAY_NEW_INT(n_ifs);
 
     if (nameArray == nil || addressArray == nil) {
-	/* Creating a string wouldn/t work here */
-	error = @symbol(allocationFailure);
-	goto bad;
+        /* Creating a string wouldn/t work here */
+        error = @symbol(allocationFailure);
+        goto bad;
     }
 
     /*
@@ -7829,38 +7830,38 @@
     countOfIf = 0;
 
     for (i=0, ifr = ifc.ifc_req; i < n_ifs; i++) {
-	/*
-	** Get Flags for this interface
-	*/
-
-	memcpy(&ifreq, ifr, sizeof(ifreq));
-	/*
-	** Get address for this interface
-	*/
-	memcpy(&ifreq, ifr, sizeof(ifreq));
-	if (ioctl (afinet_socket, SIOCGIFADDR, &ifreq) >= 0) {
-	    t = __MKBYTEARRAY((char *)&ifreq.ifr_addr, sizeof(ifreq.ifr_addr));
-	    __arrayVal(addressArray)[countOfIf] = t; __STORE(addressArray, t);
-	    t = __MKSTRING(&ifreq.ifr_name);
-	    __arrayVal(nameArray)[countOfIf] = t; __STORE(nameArray, t);
-	    countOfIf += 1;
-	}
-	// see (sigh) comment above
+        /*
+        ** Get Flags for this interface
+        */
+
+        memcpy(&ifreq, ifr, sizeof(ifreq));
+        /*
+        ** Get address for this interface
+        */
+        memcpy(&ifreq, ifr, sizeof(ifreq));
+        if (ioctl (afinet_socket, SIOCGIFADDR, &ifreq) >= 0) {
+            t = __MKBYTEARRAY((char *)&ifreq.ifr_addr, sizeof(ifreq.ifr_addr));
+            __arrayVal(addressArray)[countOfIf] = t; __STORE(addressArray, t);
+            t = __MKSTRING(&ifreq.ifr_name);
+            __arrayVal(nameArray)[countOfIf] = t; __STORE(nameArray, t);
+            countOfIf += 1;
+        }
+        // see (sigh) comment above
 #ifndef __osx__
-	ifr++;
+        ifr++;
 #else
-	{
-	    int sz = IFNAMSIZ + ifr->ifr_addr.sa_len;
-
-	    ifr = (struct ifreq *)( ((char *)ifr)+sz );
-	}
+        {
+            int sz = IFNAMSIZ + ifr->ifr_addr.sa_len;
+
+            ifr = (struct ifreq *)( ((char *)ifr)+sz );
+        }
 #endif
     }
 
     noOfIf = __mkSmallInteger(countOfIf);
 bad:
     if (afinet_socket >= 0)
-	close(afinet_socket);
+        close(afinet_socket);
 #else
     error = @symbol(notSupported);
 #endif /* defined(SIOCGIFADDR) */
@@ -7868,14 +7869,14 @@
 
     retDictionary := Dictionary new:noOfIf.
     error notNil ifTrue:[
-	self primitiveFailed:error.
-	"return empty dictionary if proceed from error"
-	^  retDictionary.
+        self primitiveFailed:error.
+        "return empty dictionary if proceed from error"
+        ^  retDictionary.
     ].
 
     1 to:noOfIf do:[:cnt|
-	"take the first address, if there is more than one!!"
-	retDictionary at:(nameArray at:cnt) ifAbsentPut:(SocketAddress fromBytes:(addressArray at:cnt)).
+        "take the first address, if there is more than one!!"
+        retDictionary at:(nameArray at:cnt) ifAbsentPut:(SocketAddress fromBytes:(addressArray at:cnt)).
     ].
 
     ^ retDictionary
@@ -7887,8 +7888,8 @@
 
 getNetworkMACAddresses
     "return a dictionary filled with
-	key -> name of interface
-	value -> the MAC adress (as ByteArray)
+        key -> name of interface
+        value -> the MAC adress (as ByteArray)
      for each interface"
 
     |addressArray nameArray noOfIf retDictionary error|
@@ -7911,8 +7912,8 @@
 
     afinet_socket = socket(AF_INET, SOCK_DGRAM, 0);
     if (afinet_socket < 0) {
-	error = __MKSTRING("Cannot open socket");
-	goto bad;
+        error = __MKSTRING("Cannot open socket");
+        goto bad;
     }
 
     /*
@@ -7923,8 +7924,8 @@
     ifc.ifc_buf = (caddr_t) buf;
 
     if (ioctl (afinet_socket, SIOCGIFCONF, (caddr_t) &ifc) < 0) {
-	error = __MKSTRING("ioctl(SIOCGIFCONF) failed");
-	goto bad;
+        error = __MKSTRING("ioctl(SIOCGIFCONF) failed");
+        goto bad;
     }
 
     // get the number of interfaces in the returned structure
@@ -7940,19 +7941,19 @@
     n_ifs = ifc.ifc_len / sizeof (struct ifreq);
 #else
     {
-	unsigned char *cp = buf;
-	char *limit = buf + ifc.ifc_len;
-
-	n_ifs = 0;
-	while (cp < limit) {
-	    int sz;
-
-	    ifr = (struct ifreq *)cp;
-	    sz = IFNAMSIZ + ifr->ifr_addr.sa_len;
-
-	    cp += sz;
-	    n_ifs++;
-	}
+        unsigned char *cp = buf;
+        char *limit = buf + ifc.ifc_len;
+
+        n_ifs = 0;
+        while (cp < limit) {
+            int sz;
+
+            ifr = (struct ifreq *)cp;
+            sz = IFNAMSIZ + ifr->ifr_addr.sa_len;
+
+            cp += sz;
+            n_ifs++;
+        }
     }
 #endif
 
@@ -7960,9 +7961,9 @@
     addressArray = __ARRAY_NEW_INT(n_ifs);
 
     if (nameArray == nil || addressArray == nil) {
-	/* Creating a string wouldn/t work here */
-	error = @symbol(allocationFailure);
-	goto bad;
+        /* Creating a string wouldn/t work here */
+        error = @symbol(allocationFailure);
+        goto bad;
     }
 
     /*
@@ -7973,107 +7974,107 @@
     countOfIf = 0;
 
     for (i=0, ifr = ifc.ifc_req; i < n_ifs; i++) {
-	/*
-	** Get Flags for this interface
-	*/
+        /*
+        ** Get Flags for this interface
+        */
 
 # ifndef __osx__ // SIOCGIFFLAGS fails on osx (Q@sv: what is this needed for anyway?)
-	{
-	    struct ifreq ifreq;
-	    memcpy(&ifreq, ifr, sizeof(ifreq));
-	    if (ioctl (afinet_socket, SIOCGIFFLAGS, &ifreq) < 0) {
-		if (@global(InfoPrinting) == true) {
-		    fprintf(stderr, "OS [warning]: ioctl(SIOCGIFFLAGS) failed");
-		}
-	    }
-	}
-# endif
-	{
+        {
+            struct ifreq ifreq;
+            memcpy(&ifreq, ifr, sizeof(ifreq));
+            if (ioctl (afinet_socket, SIOCGIFFLAGS, &ifreq) < 0) {
+                if (@global(InfoPrinting) == true) {
+                    fprintf(stderr, "OS [warning]: ioctl(SIOCGIFFLAGS) failed");
+                }
+            }
+        }
+# endif
+        {
 # ifdef SIOCGIFHWADDR
-	    /*
-	    ** Get Hardware address for this interface
-	    */
-	    {
-		struct ifreq ifreq;
-		memcpy(&ifreq, ifr, sizeof(ifreq));
-		if (ioctl (afinet_socket, SIOCGIFHWADDR, &ifreq) >= 0) {
-		    t = __MKBYTEARRAY(&ifreq.ifr_hwaddr.sa_data, IFHWADDRLEN);
-		    __arrayVal(addressArray)[countOfIf] = t; __STORE(addressArray, t);
-		    t = __MKSTRING(&ifreq.ifr_name);
-		    __arrayVal(nameArray)[countOfIf] = t; __STORE(nameArray, t);
-		    countOfIf += 1;
-		}
-	    }
+            /*
+            ** Get Hardware address for this interface
+            */
+            {
+                struct ifreq ifreq;
+                memcpy(&ifreq, ifr, sizeof(ifreq));
+                if (ioctl (afinet_socket, SIOCGIFHWADDR, &ifreq) >= 0) {
+                    t = __MKBYTEARRAY(&ifreq.ifr_hwaddr.sa_data, IFHWADDRLEN);
+                    __arrayVal(addressArray)[countOfIf] = t; __STORE(addressArray, t);
+                    t = __MKSTRING(&ifreq.ifr_name);
+                    __arrayVal(nameArray)[countOfIf] = t; __STORE(nameArray, t);
+                    countOfIf += 1;
+                }
+            }
 
 #else
-	    // macosx has no SIOCGIFHWADDR
-	    // printf("family: %d\n", ifr->ifr_addr.sa_family);
-	    // printf("name: %s\n", ifr->ifr_name);
-
-	    if (ifr->ifr_addr.sa_family == AF_LINK) {
-		struct sockaddr_dl *sdl;
-		char *adr;
-		extern char *ether_ntoa();
-		unsigned char mac[6];
-		int a,b,c,d,e,f;
-
-		sdl = (struct sockaddr_dl *)&(ifr->ifr_addr);
-		adr = ether_ntoa(LLADDR(sdl));
-		// printf("name: %s adr: %s\n", ifr->ifr_name, adr);
-		sscanf(adr, "%x:%x:%x:%x:%x:%x", &a, &b, &c, &d, &e, &f);
-		mac[0] = a;
-		mac[1] = b;
-		mac[2] = c;
-		mac[3] = d;
-		mac[4] = e;
-		mac[5] = f;
-
-		t = __MKBYTEARRAY(mac, 6);
-		__arrayVal(addressArray)[countOfIf] = t; __STORE(addressArray, t);
-		t = __MKSTRING(ifr->ifr_name);
-		__arrayVal(nameArray)[countOfIf] = t; __STORE(nameArray, t);
-		countOfIf += 1;
-	    }
-#endif
-	}
-
-	// see (sigh) comment above
+            // macosx has no SIOCGIFHWADDR
+            // printf("family: %d\n", ifr->ifr_addr.sa_family);
+            // printf("name: %s\n", ifr->ifr_name);
+
+            if (ifr->ifr_addr.sa_family == AF_LINK) {
+                struct sockaddr_dl *sdl;
+                char *adr;
+                extern char *ether_ntoa();
+                unsigned char mac[6];
+                int a,b,c,d,e,f;
+
+                sdl = (struct sockaddr_dl *)&(ifr->ifr_addr);
+                adr = ether_ntoa(LLADDR(sdl));
+                // printf("name: %s adr: %s\n", ifr->ifr_name, adr);
+                sscanf(adr, "%x:%x:%x:%x:%x:%x", &a, &b, &c, &d, &e, &f);
+                mac[0] = a;
+                mac[1] = b;
+                mac[2] = c;
+                mac[3] = d;
+                mac[4] = e;
+                mac[5] = f;
+
+                t = __MKBYTEARRAY(mac, 6);
+                __arrayVal(addressArray)[countOfIf] = t; __STORE(addressArray, t);
+                t = __MKSTRING(ifr->ifr_name);
+                __arrayVal(nameArray)[countOfIf] = t; __STORE(nameArray, t);
+                countOfIf += 1;
+            }
+#endif
+        }
+
+        // see (sigh) comment above
 #ifndef __osx__
-	ifr++;
+        ifr++;
 #else
-	{
-	    int sz = IFNAMSIZ + ifr->ifr_addr.sa_len;
-
-	    ifr = (struct ifreq *)( ((char *)ifr)+sz );
-	}
+        {
+            int sz = IFNAMSIZ + ifr->ifr_addr.sa_len;
+
+            ifr = (struct ifreq *)( ((char *)ifr)+sz );
+        }
 #endif
     }
 
     noOfIf = __mkSmallInteger(countOfIf);
 bad:
     if (afinet_socket >= 0)
-	close(afinet_socket);
+        close(afinet_socket);
 #else
     error = @symbol(notSupported);
 #endif /* SIOCGIFHWADDR */
 %}.
 
     error notNil ifTrue:[
-	self primitiveFailed:error.
-	"return an empty dictionary if proceed from error"
-	^  Dictionary new.
+        self primitiveFailed:error.
+        "return an empty dictionary if proceed from error"
+        ^  Dictionary new.
     ].
 
     "we prefer OrderedDictionary here, because we want to keep the
      order as defined in the OS."
     retDictionary := OrderedDictionary new:noOfIf.
     1 to:noOfIf do:[:cnt|
-	|macAddress|
-
-	macAddress := addressArray at:cnt.
-	macAddress ~= #[0 0 0 0 0 0] ifTrue:[
-	    retDictionary at:(nameArray at:cnt) put:macAddress.
-	].
+        |macAddress|
+
+        macAddress := addressArray at:cnt.
+        macAddress ~= #[0 0 0 0 0 0] ifTrue:[
+            retDictionary at:(nameArray at:cnt) put:macAddress.
+        ].
     ].
 
     ^ retDictionary
@@ -8115,20 +8116,20 @@
     "if supported by the OS, return the systemID;
      a unique per machine identification.
      WARNING:
-	not all systems support this; on some, #unknown is returned."
+        not all systems support this; on some, #unknown is returned."
 
 %{  /* NOCONTEXT */
 #if defined(HAS_SYSINFO) && defined(SI_HW_SERIAL)
     {
-	char buffer[128];
-
-	buffer[0] = 0;
-	if (sysinfo(SI_HW_SERIAL, buffer, sizeof(buffer))) {
-	    buffer[127] = 0;
-	    if (strlen(buffer) > 0) {
-		RETURN(__MKSTRING(buffer));
-	    }
-	}
+        char buffer[128];
+
+        buffer[0] = 0;
+        if (sysinfo(SI_HW_SERIAL, buffer, sizeof(buffer))) {
+            buffer[127] = 0;
+            if (strlen(buffer) > 0) {
+                RETURN(__MKSTRING(buffer));
+            }
+        }
     }
 #elif defined(HAS_GETHOSTID)
     int runningId;
@@ -8145,9 +8146,9 @@
     OBJ arr;
 
     if ((retVal = syssgi(SGI_SYSID, idBuffer)) == 0) {
-	arr = __BYTEARRAY_UNINITIALIZED_NEW_INT(MAXSYSIDSIZE);
-	bcopy(idBuffer, __byteArrayVal(arr), MAXSYSIDSIZE);
-	RETURN (arr);
+        arr = __BYTEARRAY_UNINITIALIZED_NEW_INT(MAXSYSIDSIZE);
+        bcopy(idBuffer, __byteArrayVal(arr), MAXSYSIDSIZE);
+        RETURN (arr);
     }
 #endif
 %}.
@@ -8171,56 +8172,56 @@
        This method is mainly provided to augment error reports with some system
        information.
        (in case of system/version specific OS errors, conditional workarounds and patches
-	may be based upon this info).
+        may be based upon this info).
        Also, applications could enable/disable buffering or otherwise reduce
        their memory usage depending upon the amount of memory installed.
        Your application may make use of available information for tuning,
        but should NEVER DEPEND upon this in any way.
 
      The returned info may (or may not) contain:
-	#system -> some operating system identification (irix, Linux, nt, win32s ...)
-	#version -> OS version (some os version identification)
-	#release -> OS release (3.5, 1.2.1 ...)
-	#node   -> some host identification (hostname)
-	#domain  -> domain name (hosts domain)
-	#machine -> type of CPU (i586, mips ...)
+        #system -> some operating system identification (irix, Linux, nt, win32s ...)
+        #version -> OS version (some os version identification)
+        #release -> OS release (3.5, 1.2.1 ...)
+        #node   -> some host identification (hostname)
+        #domain  -> domain name (hosts domain)
+        #machine -> type of CPU (i586, mips ...)
 
      those are currently returned on some machines (no warranty)
      linux:
-	#totalRam         -> total amount of memory available
-	#sharedRam        -> amount of memory which is shared among processes
-			     (i.e. shared code)
-	#bufferRam        -> amount used for buffers
-	#swapSize         -> total size of swap space
-	#freeSwap         -> free amount in swapSpace
-	#numberOfCPUs     -> number of cpus in box
-	#extendedInstructions -> extended instruction set info
+        #totalRam         -> total amount of memory available
+        #sharedRam        -> amount of memory which is shared among processes
+                             (i.e. shared code)
+        #bufferRam        -> amount used for buffers
+        #swapSize         -> total size of swap space
+        #freeSwap         -> free amount in swapSpace
+        #numberOfCPUs     -> number of cpus in box
+        #extendedInstructions -> extended instruction set info
 
      osf:
-	#physicalRam      -> total amount of physical memory
-	#cpuType          -> type of cpu (more detailed than machine)
-	#numberOfCPUs     -> number of cpus in box
+        #physicalRam      -> total amount of physical memory
+        #cpuType          -> type of cpu (more detailed than machine)
+        #numberOfCPUs     -> number of cpus in box
 
      osx:
-	#physicalRam      -> total amount of physical memory
+        #physicalRam      -> total amount of physical memory
 
      solaris:
-	#physicalRam      -> total amount of physical memory
-	#availableRam     -> total available amount of physical memory (i.e. unused ram)
-	#freeRam          -> amount of free memory
-	#numberOfCPUs     -> number of cpus in box (online CPUS)
-	[#dCacheSize]     -> bytes in data cache (only available on some solaris versions)
-	[#iCacheSize]     -> bytes in data cache (only available on some solaris versions)
-	[#instructionSets]-> instruction sets available (only available on some solaris versions)
-	[#platform]       -> platform name (only available on some solaris versions)
+        #physicalRam      -> total amount of physical memory
+        #availableRam     -> total available amount of physical memory (i.e. unused ram)
+        #freeRam          -> amount of free memory
+        #numberOfCPUs     -> number of cpus in box (online CPUS)
+        [#dCacheSize]     -> bytes in data cache (only available on some solaris versions)
+        [#iCacheSize]     -> bytes in data cache (only available on some solaris versions)
+        [#instructionSets]-> instruction sets available (only available on some solaris versions)
+        [#platform]       -> platform name (only available on some solaris versions)
 
      hpux:
-	#physicalRam      -> total amount of physical memory in box
-	#activeRealMemory -> ? - read pstat documentation
-	#activeVirtualRam -> ? - read pstat documentation
-	#freeMemory       -> ? - read pstat documentation
-	#realMemory       -> ? (amount of memory left to user programs)
-	#virtualRam       -> ? - read pstat documentation
+        #physicalRam      -> total amount of physical memory in box
+        #activeRealMemory -> ? - read pstat documentation
+        #activeVirtualRam -> ? - read pstat documentation
+        #freeMemory       -> ? - read pstat documentation
+        #realMemory       -> ? (amount of memory left to user programs)
+        #virtualRam       -> ? - read pstat documentation
     "
 
     |sys node rel ver mach dom mtyp brel info arch cpuType cpuSpeed
@@ -8238,11 +8239,11 @@
     struct sysinfo infoBuffer;
 
     if (sysinfo(&infoBuffer) >= 0) {
-	totalRam   = __MKUINT(infoBuffer.totalram);
-	sharedRam = __MKUINT(infoBuffer.sharedram);
-	bufferRam = __MKUINT(infoBuffer.bufferram);
-	swapSize  = __MKUINT(infoBuffer.totalswap);
-	freeSwap  = __MKUINT(infoBuffer.freeswap);
+        totalRam   = __MKUINT(infoBuffer.totalram);
+        sharedRam = __MKUINT(infoBuffer.sharedram);
+        bufferRam = __MKUINT(infoBuffer.bufferram);
+        swapSize  = __MKUINT(infoBuffer.totalswap);
+        freeSwap  = __MKUINT(infoBuffer.freeswap);
     }
 # endif
 #endif /* LINUX */
@@ -8269,18 +8270,18 @@
 
 #if defined(HAS_UNAME)
     {
-	struct utsname ubuff;
-
-	if (uname(&ubuff) >= 0) {
-	    sys  = __MKSTRING(ubuff.sysname);
-	    node = __MKSTRING(ubuff.nodename);
-	    rel  = __MKSTRING(ubuff.release);
-	    ver  = __MKSTRING(ubuff.version);
-	    mach = __MKSTRING(ubuff.machine);
+        struct utsname ubuff;
+
+        if (uname(&ubuff) >= 0) {
+            sys  = __MKSTRING(ubuff.sysname);
+            node = __MKSTRING(ubuff.nodename);
+            rel  = __MKSTRING(ubuff.release);
+            ver  = __MKSTRING(ubuff.version);
+            mach = __MKSTRING(ubuff.machine);
 # if defined(HAS_UTS_DOMAINNAME) || defined(_GNU_SOURCE)
-	    dom  = __MKSTRING(ubuff.domainname);
+            dom  = __MKSTRING(ubuff.domainname);
 # endif /* no HAS_UTS_DOMAINNAME */
-	}
+        }
     }
 
 #else /* no UNAME */
@@ -8293,41 +8294,41 @@
 #if defined(HAS_SYSINFO)
 # if defined(SI_ARCHITECTURE)
     if (arch == nil) {
-	char buffer[128];
-
-	if (sysinfo(SI_ARCHITECTURE, buffer, sizeof(buffer))) {
-	    arch = __MKSTRING(buffer);
-	}
+        char buffer[128];
+
+        if (sysinfo(SI_ARCHITECTURE, buffer, sizeof(buffer))) {
+            arch = __MKSTRING(buffer);
+        }
     }
 # endif /* SI_ARCHITECTURE */
 
 # if defined(SI_ISALIST)
     {
-	char buffer[128];
-
-	if (sysinfo(SI_ISALIST, buffer, sizeof(buffer))) {
-	    instructionSets = __MKSTRING(buffer);
-	}
+        char buffer[128];
+
+        if (sysinfo(SI_ISALIST, buffer, sizeof(buffer))) {
+            instructionSets = __MKSTRING(buffer);
+        }
     }
 # endif /* SI_ISALIST */
 
 # if defined(SI_PLATFORM)
     {
-	char buffer[128];
-
-	if (sysinfo(SI_PLATFORM, buffer, sizeof(buffer))) {
-	    platform = __MKSTRING(buffer);
-	}
+        char buffer[128];
+
+        if (sysinfo(SI_PLATFORM, buffer, sizeof(buffer))) {
+            platform = __MKSTRING(buffer);
+        }
     }
 # endif /* SI_PLATFORM */
 
 # if defined(SI_RELEASE)
     {
-	char buffer[128];
-
-	if (sysinfo(SI_RELEASE, buffer, sizeof(buffer))) {
-	    rel = __MKSTRING(buffer);
-	}
+        char buffer[128];
+
+        if (sysinfo(SI_RELEASE, buffer, sizeof(buffer))) {
+            rel = __MKSTRING(buffer);
+        }
     }
 # endif /* SI_RELEASE */
 #endif /* HAS_SYSINFO */
@@ -8335,426 +8336,426 @@
 #if defined(HAS_SYSCONF)
 # ifdef _SC_NPROCESSORS_ONLN
     {
-	long val;
-
-	val = sysconf(_SC_NPROCESSORS_ONLN);
-	if (val > 0) {
-	    numberOfCPUs = __MKINT(val);
-	}
+        long val;
+
+        val = sysconf(_SC_NPROCESSORS_ONLN);
+        if (val > 0) {
+            numberOfCPUs = __MKINT(val);
+        }
     }
 # endif
 # ifdef _SC_NPROCESSORS_CONF
     {
-	long val;
-
-	val = sysconf(_SC_NPROCESSORS_CONF);
-	if (val > 0) {
-	    numberOfPhysicalCPUs = __MKINT(val);
-	}
+        long val;
+
+        val = sysconf(_SC_NPROCESSORS_CONF);
+        if (val > 0) {
+            numberOfPhysicalCPUs = __MKINT(val);
+        }
     }
 # endif
 
 # if defined(_SC_PAGESIZE)
     {
-	long val;
-
-	val = sysconf(_SC_PAGESIZE);
-	if (val != -1) {
-	    pageSize = __MKUINT(val);
-	}
+        long val;
+
+        val = sysconf(_SC_PAGESIZE);
+        if (val != -1) {
+            pageSize = __MKUINT(val);
+        }
     }
 # endif
 
 # if defined(_SC_PHYS_PAGES)
     {
-	long val;
-
-	val = sysconf(_SC_PHYS_PAGES);
-	if (val != -1) {
-	    physicalPages = __MKUINT(val);
-	}
+        long val;
+
+        val = sysconf(_SC_PHYS_PAGES);
+        if (val != -1) {
+            physicalPages = __MKUINT(val);
+        }
     }
 # endif
 
 # if defined(_SC_AVPHYS_PAGES)
     {
-	long val;
-
-	val = sysconf(_SC_AVPHYS_PAGES);
-	if (val != -1) {
-	    availablePages = __MKUINT(val);
-	}
+        long val;
+
+        val = sysconf(_SC_AVPHYS_PAGES);
+        if (val != -1) {
+            availablePages = __MKUINT(val);
+        }
     }
 # endif
 
 # if defined(_SC_ICACHE_SZ)
     {
-	long val;
-
-	val = sysconf(_SC_ICACHE_SZ);
-	if (val != -1) {
-	    iCacheSize = __MKUINT(val);
-	}
+        long val;
+
+        val = sysconf(_SC_ICACHE_SZ);
+        if (val != -1) {
+            iCacheSize = __MKUINT(val);
+        }
     }
 # endif
 
 # if defined(_SC_DCACHE_SZ)
     {
-	long val;
-
-	val = sysconf(_SC_DCACHE_SZ);
-	if (val != -1) {
-	    dCacheSize = __MKUINT(val);
-	}
+        long val;
+
+        val = sysconf(_SC_DCACHE_SZ);
+        if (val != -1) {
+            dCacheSize = __MKUINT(val);
+        }
     }
 # endif
 #endif /* HAS_SYSCONF */
 
 #if defined(HAS_GETSYSINFO)
     {
-	INT index;
-	int retInt32 = 0;
+        INT index;
+        int retInt32 = 0;
 
 # if defined(GSI_CPU)
-	index = 0;
-	if (getsysinfo(GSI_CPU, &retInt32, sizeof(retInt32), &index, NULL) > 0) {
-	    switch (retInt32) {
+        index = 0;
+        if (getsysinfo(GSI_CPU, &retInt32, sizeof(retInt32), &index, NULL) > 0) {
+            switch (retInt32) {
 #  ifdef VAX_780
-		case VAX_780:
-		    cpuType = __MKSTRING("VAX_780");
-		    break;
+                case VAX_780:
+                    cpuType = __MKSTRING("VAX_780");
+                    break;
 #  endif
 #  ifdef VAX_750
-		case VAX_750:
-		    cpuType = __MKSTRING("VAX_750");
-		    break;
+                case VAX_750:
+                    cpuType = __MKSTRING("VAX_750");
+                    break;
 #  endif
 #  ifdef VAX_730
-		case VAX_730:
-		    cpuType = __MKSTRING("VAX_730");
-		    break;
+                case VAX_730:
+                    cpuType = __MKSTRING("VAX_730");
+                    break;
 #  endif
 #  ifdef VAX_8600
-		case VAX_8600:
-		    cpuType = __MKSTRING("VAX_8600");
-		    break;
+                case VAX_8600:
+                    cpuType = __MKSTRING("VAX_8600");
+                    break;
 #  endif
 #  ifdef VAX_8200
-		case VAX_8200:
-		    cpuType = __MKSTRING("VAX_8200");
-		    break;
+                case VAX_8200:
+                    cpuType = __MKSTRING("VAX_8200");
+                    break;
 #  endif
 #  ifdef VAX_8800
-		case VAX_8800:
-		    cpuType = __MKSTRING("VAX_8800");
-		    break;
+                case VAX_8800:
+                    cpuType = __MKSTRING("VAX_8800");
+                    break;
 #  endif
 #  ifdef MVAX_I
-		case MVAX_I:
-		    cpuType = __MKSTRING("MVAX_I");
-		    break;
+                case MVAX_I:
+                    cpuType = __MKSTRING("MVAX_I");
+                    break;
 #  endif
 #  ifdef MVAX_II
-		case MVAX_II:
-		    cpuType = __MKSTRING("MVAX_II");
-		    break;
+                case MVAX_II:
+                    cpuType = __MKSTRING("MVAX_II");
+                    break;
 #  endif
 #  ifdef V_VAX
-		case V_VAX:
-		    cpuType = __MKSTRING("V_VAX");
-		    break;
+                case V_VAX:
+                    cpuType = __MKSTRING("V_VAX");
+                    break;
 #  endif
 #  ifdef VAX_3600
-		case VAX_3600:
-		    cpuType = __MKSTRING("VAX_3600");
-		    break;
+                case VAX_3600:
+                    cpuType = __MKSTRING("VAX_3600");
+                    break;
 #  endif
 #  ifdef VAX_6200
-		case VAX_6200:
-		    cpuType = __MKSTRING("VAX_6200");
-		    break;
+                case VAX_6200:
+                    cpuType = __MKSTRING("VAX_6200");
+                    break;
 #  endif
 #  ifdef VAX_3400
-		case VAX_3400:
-		    cpuType = __MKSTRING("VAX_3400");
-		    break;
+                case VAX_3400:
+                    cpuType = __MKSTRING("VAX_3400");
+                    break;
 #  endif
 #  ifdef C_VAXSTAR
-		case C_VAXSTAR:
-		    cpuType = __MKSTRING("C_VAXSTAR");
-		    break;
+                case C_VAXSTAR:
+                    cpuType = __MKSTRING("C_VAXSTAR");
+                    break;
 #  endif
 #  ifdef VAX_60
-		case VAX_60:
-		    cpuType = __MKSTRING("VAX_60");
-		    break;
+                case VAX_60:
+                    cpuType = __MKSTRING("VAX_60");
+                    break;
 #  endif
 #  ifdef VAX_3900
-		case VAX_3900:
-		    cpuType = __MKSTRING("VAX_3900");
-		    break;
+                case VAX_3900:
+                    cpuType = __MKSTRING("VAX_3900");
+                    break;
 #  endif
 #  ifdef DS_3100
-		case DS_3100:
-		    cpuType = __MKSTRING("DS_3100");
-		    break;
+                case DS_3100:
+                    cpuType = __MKSTRING("DS_3100");
+                    break;
 #  endif
 #  ifdef VAX_8820
-		case VAX_8820:
-		    cpuType = __MKSTRING("VAX_8820");
-		    break;
+                case VAX_8820:
+                    cpuType = __MKSTRING("VAX_8820");
+                    break;
 #  endif
 #  ifdef DS_5400
-		case DS_5400:
-		    cpuType = __MKSTRING("DS_5400");
-		    break;
+                case DS_5400:
+                    cpuType = __MKSTRING("DS_5400");
+                    break;
 #  endif
 #  ifdef DS_5800
-		case DS_5800:
-		    cpuType = __MKSTRING("DS_5800");
-		    break;
+                case DS_5800:
+                    cpuType = __MKSTRING("DS_5800");
+                    break;
 #  endif
 #  ifdef DS_5000
-		case DS_5000:
-		    cpuType = __MKSTRING("DS_5000");
-		    break;
+                case DS_5000:
+                    cpuType = __MKSTRING("DS_5000");
+                    break;
 #  endif
 #  ifdef DS_CMAX
-		case DS_CMAX:
-		    cpuType = __MKSTRING("DS_CMAX");
-		    break;
+                case DS_CMAX:
+                    cpuType = __MKSTRING("DS_CMAX");
+                    break;
 #  endif
 #  ifdef VAX_6400
-		case VAX_6400:
-		    cpuType = __MKSTRING("VAX_6400");
-		    break;
+                case VAX_6400:
+                    cpuType = __MKSTRING("VAX_6400");
+                    break;
 #  endif
 #  ifdef VAXSTAR
-		case VAXSTAR:
-		    cpuType = __MKSTRING("VAXSTAR");
-		    break;
+                case VAXSTAR:
+                    cpuType = __MKSTRING("VAXSTAR");
+                    break;
 #  endif
 #  ifdef DS_5500
-		case DS_5500:
-		    cpuType = __MKSTRING("DS_5500");
-		    break;
+                case DS_5500:
+                    cpuType = __MKSTRING("DS_5500");
+                    break;
 #  endif
 #  ifdef DS_5100
-		case DS_5100:
-		    cpuType = __MKSTRING("DS_5100");
-		    break;
+                case DS_5100:
+                    cpuType = __MKSTRING("DS_5100");
+                    break;
 #  endif
 #  ifdef VAX_9000
-		case VAX_9000:
-		    cpuType = __MKSTRING("VAX_9000");
-		    break;
+                case VAX_9000:
+                    cpuType = __MKSTRING("VAX_9000");
+                    break;
 #  endif
 #  ifdef DS_500_100
-		case DS_500_100:
-		    cpuType = __MKSTRING("DS_500_100");
-		    break;
+                case DS_500_100:
+                    cpuType = __MKSTRING("DS_500_100");
+                    break;
 #  endif
 
 
 #  ifdef ALPHA_ADU
-		case ALPHA_ADU:
-		    cpuType = __MKSTRING("ALPHA_ADU");
-		    break;
+                case ALPHA_ADU:
+                    cpuType = __MKSTRING("ALPHA_ADU");
+                    break;
 #  endif
 #  ifdef DEC_4000
-		case DEC_4000:
-		    cpuType = __MKSTRING("DEC_4000");
-		    break;
+                case DEC_4000:
+                    cpuType = __MKSTRING("DEC_4000");
+                    break;
 #  endif
 #  ifdef DEC_3000_500
-		case DEC_3000_500:
-		    cpuType = __MKSTRING("DEC_3000_500");
-		    break;
+                case DEC_3000_500:
+                    cpuType = __MKSTRING("DEC_3000_500");
+                    break;
 #  endif
 #  ifdef DEC_7000
-		case DEC_7000:
-		    cpuType = __MKSTRING("DEC_7000");
-		    break;
+                case DEC_7000:
+                    cpuType = __MKSTRING("DEC_7000");
+                    break;
 #  endif
 #  ifdef DS_5000_300
-		case DS_5000_300:
-		    cpuType = __MKSTRING("DS_5000_300");
-		    break;
+                case DS_5000_300:
+                    cpuType = __MKSTRING("DS_5000_300");
+                    break;
 #  endif
 #  ifdef DEC_3000_300
-		case DEC_3000_300:
-		    cpuType = __MKSTRING("DEC_3000_300");
-		    break;
+                case DEC_3000_300:
+                    cpuType = __MKSTRING("DEC_3000_300");
+                    break;
 #  endif
 #  ifdef DEC_2000_300
-		case DEC_2000_300:
-		    cpuType = __MKSTRING("DEC_2000_300");
-		    break;
+                case DEC_2000_300:
+                    cpuType = __MKSTRING("DEC_2000_300");
+                    break;
 #  endif
 #  ifdef DEC_2100_A500
-		case DEC_2100_A500:
-		    cpuType = __MKSTRING("DEC_2100_A500");
-		    break;
+                case DEC_2100_A500:
+                    cpuType = __MKSTRING("DEC_2100_A500");
+                    break;
 #  endif
 #  ifdef DEC_2100_A50
-		case DEC_2100_A50:
-		    cpuType = __MKSTRING("DEC_2100_A50");
-		    break;
+                case DEC_2100_A50:
+                    cpuType = __MKSTRING("DEC_2100_A50");
+                    break;
 #  endif
 #  ifdef ALPHA_KN20AA
-		case ALPHA_KN20AA:
-		    cpuType = __MKSTRING("ALPHA_KN20AA");
-		    break;
+                case ALPHA_KN20AA:
+                    cpuType = __MKSTRING("ALPHA_KN20AA");
+                    break;
 #  endif
 #  ifdef DEC_21000
-		case DEC_21000:
-		    cpuType = __MKSTRING("DEC_21000");
-		    break;
+                case DEC_21000:
+                    cpuType = __MKSTRING("DEC_21000");
+                    break;
 #  endif
 #  ifdef DEC_AXPVME_64
-		case DEC_AXPVME_64:
-		    cpuType = __MKSTRING("DEC_AXPVME_64");
-		    break;
+                case DEC_AXPVME_64:
+                    cpuType = __MKSTRING("DEC_AXPVME_64");
+                    break;
 #  endif
 #  ifdef DEC_2100_C500
-		case DEC_2100_C500:
-		    cpuType = __MKSTRING("DEC_2100_C500");
-		    break;
+                case DEC_2100_C500:
+                    cpuType = __MKSTRING("DEC_2100_C500");
+                    break;
 #  endif
 #  ifdef DEC_AXPPCI_33
-		case DEC_AXPPCI_33:
-		    cpuType = __MKSTRING("DEC_AXPPCI_33");
-		    break;
+                case DEC_AXPPCI_33:
+                    cpuType = __MKSTRING("DEC_AXPPCI_33");
+                    break;
 #  endif
 #  ifdef DEC_1000
-		case DEC_1000:
-		    cpuType = __MKSTRING("DEC_1000");
-		    break;
+                case DEC_1000:
+                    cpuType = __MKSTRING("DEC_1000");
+                    break;
 #  endif
 #  ifdef EB64_PLUS
-		case EB64_PLUS:
-		    cpuType = __MKSTRING("EB64_PLUS");
-		    break;
+                case EB64_PLUS:
+                    cpuType = __MKSTRING("EB64_PLUS");
+                    break;
 #  endif
 #  ifdef LCA_EB66
-		case LCA_EB66:
-		    cpuType = __MKSTRING("LCA_EB66");
-		    break;
+                case LCA_EB66:
+                    cpuType = __MKSTRING("LCA_EB66");
+                    break;
 #  endif
 #  ifdef ALPHA_EB164
-		case ALPHA_EB164:
-		    cpuType = __MKSTRING("ALPHA_EB164");
-		    break;
+                case ALPHA_EB164:
+                    cpuType = __MKSTRING("ALPHA_EB164");
+                    break;
 #  endif
 #  ifdef DEC_EV45_PBP
-		case DEC_EV45_PBP:
-		    cpuType = __MKSTRING("DEC_EV45_PBP");
-		    break;
+                case DEC_EV45_PBP:
+                    cpuType = __MKSTRING("DEC_EV45_PBP");
+                    break;
 #  endif
 #  ifdef DEC_1000A
-		case DEC_1000A:
-		    cpuType = __MKSTRING("DEC_1000A");
-		    break;
+                case DEC_1000A:
+                    cpuType = __MKSTRING("DEC_1000A");
+                    break;
 #  endif
 #  ifdef DEC_4100
-		case DEC_4100:
-		    cpuType = __MKSTRING("DEC_4100");
-		    break;
+                case DEC_4100:
+                    cpuType = __MKSTRING("DEC_4100");
+                    break;
 #  endif
 #  ifdef DEC_ALPHAVME_224
-		case DEC_ALPHAVME_224:
-		    cpuType = __MKSTRING("DEC_ALPHAVME_224");
-		    break;
+                case DEC_ALPHAVME_224:
+                    cpuType = __MKSTRING("DEC_ALPHAVME_224");
+                    break;
 #  endif
 #  ifdef DEC_1000_5
-		case DEC_1000_5:
-		    cpuType = __MKSTRING("DEC_1000_5");
-		    break;
+                case DEC_1000_5:
+                    cpuType = __MKSTRING("DEC_1000_5");
+                    break;
 #  endif
 #  ifdef DEC_1000A_5
-		case DEC_1000A_5:
-		    cpuType = __MKSTRING("DEC_1000A_5");
-		    break;
+                case DEC_1000A_5:
+                    cpuType = __MKSTRING("DEC_1000A_5");
+                    break;
 #  endif
 #  ifdef DEC_EV56_PBP
-		case DEC_EV56_PBP:
-		    cpuType = __MKSTRING("DEC_EV56_PBP");
-		    break;
+                case DEC_EV56_PBP:
+                    cpuType = __MKSTRING("DEC_EV56_PBP");
+                    break;
 #  endif
 #  ifdef ALPHABOOK
-		case ALPHABOOK:
-		    cpuType = __MKSTRING("ALPHABOOK");
-		    break;
+                case ALPHABOOK:
+                    cpuType = __MKSTRING("ALPHABOOK");
+                    break;
 #  endif
 #  ifdef DEC_ALPHAVME_320
-		case DEC_ALPHAVME_320:
-		    cpuType = __MKSTRING("DEC_ALPHAVME_320");
-		    break;
+                case DEC_ALPHAVME_320:
+                    cpuType = __MKSTRING("DEC_ALPHAVME_320");
+                    break;
 #  endif
 #  ifdef DEC_550
-		case DEC_550:
-		    cpuType = __MKSTRING("DEC_550");
-		    break;
+                case DEC_550:
+                    cpuType = __MKSTRING("DEC_550");
+                    break;
 #  endif
 #  ifdef DEC_6600
-		case DEC_6600:
-		    cpuType = __MKSTRING("DEC_6600");
-		    break;
+                case DEC_6600:
+                    cpuType = __MKSTRING("DEC_6600");
+                    break;
 #  endif
 #  ifdef UNKN_SYSTEM
-		case UNKN_SYSTEM:
-		    cpuType = __MKSTRING("UNKN_SYSTEM");
-		    break;
-#  endif
-		default:
-		    cpuType = __MKSTRING("OTHER_DEC_SYSTEM");
-		    break;
-	    }
-	}
+                case UNKN_SYSTEM:
+                    cpuType = __MKSTRING("UNKN_SYSTEM");
+                    break;
+#  endif
+                default:
+                    cpuType = __MKSTRING("OTHER_DEC_SYSTEM");
+                    break;
+            }
+        }
 # endif /* GSI_CPU */
 
 # if defined(GSI_CPU_INFO)
-	/*
-	 * stupid: OSF1 pre V4.0 has no mhz, but V4.0 has it.
-	 * use the GSI_PLATFORM_NAME as a hint - it is only defined in
-	 * V4.0 and higher ... (sigh)
-	 */
+        /*
+         * stupid: OSF1 pre V4.0 has no mhz, but V4.0 has it.
+         * use the GSI_PLATFORM_NAME as a hint - it is only defined in
+         * V4.0 and higher ... (sigh)
+         */
 #  if defined(GSI_PLATFORM_NAME)
-	{
-	    struct cpu_info cpuInfo;
-
-	    index = 0;
-	    if (getsysinfo(GSI_CPU_INFO, &cpuInfo, sizeof(cpuInfo), &index, NULL) > 0) {
-		cpuSpeed   = __MKUINT(cpuInfo.mhz);
-	    }
-	}
+        {
+            struct cpu_info cpuInfo;
+
+            index = 0;
+            if (getsysinfo(GSI_CPU_INFO, &cpuInfo, sizeof(cpuInfo), &index, NULL) > 0) {
+                cpuSpeed   = __MKUINT(cpuInfo.mhz);
+            }
+        }
 #  endif
 # endif /* GSI_CPU_INFO */
 
 # if defined(GSI_CPUS_IN_BOX)
-	index = 0;
-	if (getsysinfo(GSI_CPUS_IN_BOX, &retInt32, sizeof(retInt32), &index, NULL) > 0) {
-	    numberOfCPUs   = __MKUINT(retInt32);
-	}
+        index = 0;
+        if (getsysinfo(GSI_CPUS_IN_BOX, &retInt32, sizeof(retInt32), &index, NULL) > 0) {
+            numberOfCPUs   = __MKUINT(retInt32);
+        }
 # endif /* GSI_CPUS_IN_BOX */
 
 # if defined(GSI_PHYSMEM)
-	index = 0;
-	if (getsysinfo(GSI_PHYSMEM, &retInt32, sizeof(retInt32), &index, NULL) > 0) {
-	    INT bytes = retInt32 * 1024;
-
-	    physicalRam   = __MKUINT(bytes);
-	}
+        index = 0;
+        if (getsysinfo(GSI_PHYSMEM, &retInt32, sizeof(retInt32), &index, NULL) > 0) {
+            INT bytes = retInt32 * 1024;
+
+            physicalRam   = __MKUINT(bytes);
+        }
 # endif /* GSI_PHYSMEM */
 
 # if defined(GSI_PLATFORM_NAME) && (!defined(HAS_SYSINFO) || !defined(SI_PLATFORM))
     {
-	char buffer[128];
-
-	index = 0;
-	if (getsysinfo(GSI_PLATFORM_NAME, buffer, sizeof(buffer), &index, NULL) > 0) {
-	    platform = __MKSTRING(buffer);
-	}
+        char buffer[128];
+
+        index = 0;
+        if (getsysinfo(GSI_PLATFORM_NAME, buffer, sizeof(buffer), &index, NULL) > 0) {
+            platform = __MKSTRING(buffer);
+        }
     }
 # endif /* GSI_PLATFORM_NAME */
 
@@ -8779,25 +8780,25 @@
 
 
     {
-	extern OBJ __getInstructionSetInfo();
-
-	extendedInstructions = __getInstructionSetInfo();
+        extern OBJ __getInstructionSetInfo();
+
+        extendedInstructions = __getInstructionSetInfo();
     }
 %}.
     sys isNil ifTrue:[
-	sys := self getSystemType.
+        sys := self getSystemType.
     ].
     node isNil ifTrue:[
-	node := self getHostName.
+        node := self getHostName.
     ].
     dom isNil ifTrue:[
-	dom := self getDomainName.
+        dom := self getDomainName.
     ].
     mach isNil ifTrue:[
-	mach := self getCPUType.
+        mach := self getCPUType.
     ].
     arch isNil ifTrue:[
-	arch := sys.
+        arch := sys.
     ].
 
     info := IdentityDictionary new.
@@ -8809,12 +8810,12 @@
     arch notNil ifTrue:[info at:#architecture put:arch].
     dom notNil ifTrue:[info at:#domain put:dom].
     (pageSize notNil and:[physicalPages notNil]) ifTrue:[
-	physicalRam := pageSize * physicalPages. "/ done here - could be largeInt.
+        physicalRam := pageSize * physicalPages. "/ done here - could be largeInt.
     ].
     physicalRam notNil ifTrue:[info at:#physicalRam put:physicalRam].
     (pageSize notNil and:[availablePages notNil]) ifTrue:[
-	availableRam := pageSize * availablePages. "/ done here - could be largeInt.
-	availableRam notNil ifTrue:[info at:#availableRam put:availableRam].
+        availableRam := pageSize * availablePages. "/ done here - could be largeInt.
+        availableRam notNil ifTrue:[info at:#availableRam put:availableRam].
     ].
     totalRam notNil ifTrue:[info at:#totalRam put:totalRam].
     sharedRam notNil ifTrue:[info at:#sharedRam put:sharedRam].
@@ -8869,7 +8870,7 @@
 
 %}.
     sys isNil ifTrue:[
-	^ self getOSType
+        ^ self getOSType
     ].
     ^ sys
 
@@ -8932,11 +8933,11 @@
 
 %{
     if (__isSmallInteger(pid)) {
-	/* in UNIX, a kill(pid, 0) is a noop used to check if a pid exists */
-	if (kill(__smallIntegerVal(pid), 0) < 0 && errno != EPERM) {
-	    RETURN ( false );
-	}
-	RETURN ( true );
+        /* in UNIX, a kill(pid, 0) is a noop used to check if a pid exists */
+        if (kill(__smallIntegerVal(pid), 0) < 0 && errno != EPERM) {
+            RETURN ( false );
+        }
+        RETURN ( true );
     }
 %}.
 
@@ -8963,11 +8964,11 @@
 maxFileNameLength
     "return the max number of characters in a filename.
      CAVEAT:
-	 Actually, the following is somewhat wrong - some systems
-	 support different sizes, depending on the volume.
-	 We return a somewhat conservative number here.
-	 Another entry, to query for volume specific max
-	 will be added in the future."
+         Actually, the following is somewhat wrong - some systems
+         support different sizes, depending on the volume.
+         We return a somewhat conservative number here.
+         Another entry, to query for volume specific max
+         will be added in the future."
 
 %{  /* NOCONTEXT */
 
@@ -9006,7 +9007,7 @@
 
      l = sysconf(_SC_OPEN_MAX);
      if (l >= 0) {
-	 RETURN(__mkSmallInteger(l));
+         RETURN(__mkSmallInteger(l));
      }
 %}.
      self primitiveFailed
@@ -9039,21 +9040,21 @@
 primGetDomainName
     "return the domain this host is in.
      Notice:
-	not all systems support this; on some, nil is returned."
+        not all systems support this; on some, nil is returned."
 
 %{  /* STACK: 2048 */
 #if defined(HAS_GETDOMAINNAME)
     char buffer[256];
 
     if (getdomainname(buffer, sizeof(buffer)) == 0) {
-	RETURN (__MKSTRING(buffer));
+        RETURN (__MKSTRING(buffer));
     }
 #else
 # if defined(HAS_UNAME) && defined(HAS_UTS_DOMAINNAME)
     struct utsname ubuff;
 
     if (uname(&ubuff) >= 0) {
-	RETURN (__MKSTRING(ubuff.domainname));
+        RETURN (__MKSTRING(ubuff.domainname));
     }
 # else
 #  if defined(HAS_SYSINFO) && defined(SI_SRPC_DOMAIN)
@@ -9061,7 +9062,7 @@
     int ret;
 
     if ((ret = sysinfo(SI_SRPC_DOMAIN, buffer, sizeof(buffer))) >= 0 && ret <= sizeof(buffer)) {
-	RETURN (__MKSTRING(buffer));
+        RETURN (__MKSTRING(buffer));
     }
 #  endif
 # endif
@@ -9080,7 +9081,7 @@
     "return the hostname we are running on - if there is
      a HOST environment variable, we are much faster here ...
      Notice:
-	not all systems support this; on some, nil is returned."
+        not all systems support this; on some, nil is returned."
 
 %{  /* STACK: 100000 */
 
@@ -9091,14 +9092,14 @@
     char buffer[256];
 
     if (gethostname(buffer, sizeof(buffer)) == 0) {
-	RETURN (__MKSTRING(buffer));
+        RETURN (__MKSTRING(buffer));
     }
 #else
 # if defined(HAS_UNAME)
     struct utsname ubuff;
 
     if (uname(&ubuff) >= 0) {
-	RETURN (__MKSTRING(ubuff.nodename));
+        RETURN (__MKSTRING(ubuff.nodename));
     }
 # else
 #  if defined(HAS_SYSINFO) && defined(SI_HOSTNAME)
@@ -9106,7 +9107,7 @@
     int ret;
 
     if ((ret = sysinfo(SI_HOSTNAME, buffer, sizeof(buffer))) >= 0 && ret <= sizeof(buffer)) {
-	RETURN (__MKSTRING(buffer));
+        RETURN (__MKSTRING(buffer));
     }
 #  endif
 # endif
@@ -9121,11 +9122,11 @@
 
 randomBytesInto:bufferOrInteger
     "If bufferOrInteger is a String or a ByteArray,
-	fill a given buffer with random bytes from the RtlGenRandom function
-	and answer the buffer.
+        fill a given buffer with random bytes from the RtlGenRandom function
+        and answer the buffer.
 
      If bufferOrInteger is a SmallInteger,
-	return this many bytes (max 4) as a SmallInteger.
+        return this many bytes (max 4) as a SmallInteger.
 
      Return nil on error (may raise PrimitiveFailure, too).
 
@@ -9142,18 +9143,18 @@
     char *buffer;
 
     if (__isSmallInteger(bufferOrInteger) && (wanted = __smallIntegerVal(bufferOrInteger) <= 4)) {
-	int buf = 0;
-
-	do {
-	    cnt = getrandom(&buf + gotSoFar, wanted - gotSoFar, 0);
-	    if (cnt < 0) {
+        int buf = 0;
+
+        do {
+            cnt = getrandom(&buf + gotSoFar, wanted - gotSoFar, 0);
+            if (cnt < 0) {
 		if (errno != EINTR && errno != EAGAIN)
-		    goto error;
-	    } else {
-		gotSoFar = gotSoFar + cnt;
-	    }
-	} while (gotSoFar < wanted);
-	RETURN(__mkSmallInteger(buf));
+                    goto error;
+            } else {
+                gotSoFar = gotSoFar + cnt;
+            }
+        } while (gotSoFar < wanted);
+        RETURN(__mkSmallInteger(buf));
     } else if (__isByteArray(bufferOrInteger)) {
 	wanted = __byteArraySize(bufferOrInteger);
 	buffer = __byteArrayVal(bufferOrInteger);
@@ -9161,18 +9162,18 @@
 	wanted = __stringSize(bufferOrInteger);
 	buffer = __stringVal(bufferOrInteger);
     } else
-	goto error;
+        goto error;
 
     do {
-	cnt = getrandom(buffer + gotSoFar, wanted - gotSoFar, 0);
-	if (cnt < 0) {
+        cnt = getrandom(buffer + gotSoFar, wanted - gotSoFar, 0);
+        if (cnt < 0) {
 	    if (errno != EINTR && errno != EAGAIN)
-		goto error;
+                goto error;
 	    buffer = __isByteArray(bufferOrInteger) ?
 			__byteArrayVal(bufferOrInteger) : __stringVal(bufferOrInteger);
-	} else {
-	    gotSoFar = gotSoFar + cnt;
-	}
+        } else {
+            gotSoFar = gotSoFar + cnt;
+        }
     } while (gotSoFar < wanted);
     RETURN(bufferOrInteger);
 
@@ -9184,9 +9185,9 @@
     ^ self primitiveFailed.
 
     "
-	self randomBytesInto:2.
-	self randomBytesInto:(ByteArray new:16).
-	self randomBytesInto:(String new:16).
+        self randomBytesInto:2.
+        self randomBytesInto:(ByteArray new:16).
+        self randomBytesInto:(String new:16).
     "
 !
 
@@ -9203,30 +9204,30 @@
     int valueSize;
 
     if (__isStringLike(aKeyStringOrSymbol)) {
-	if (aString == nil) {
-	    /* env used only temporary for deregistration */
-	    valueSize = 0;
-	    env = __stringVal(aKeyStringOrSymbol);
-	} else if (__isStringLike(aString)) {
-	    /* have to use stable memory for env */
-	    valueSize = __stringSize(aString);
-	    env = (char *)malloc(__stringSize(aKeyStringOrSymbol) + valueSize + 2);
-	    if (env == 0)
-		goto err;
-	    strcpy(env, __stringVal(aKeyStringOrSymbol));
-	    strcat(env, "=");
-	    strncat(env, __stringVal(aString), valueSize);
-	} else
-	    goto err;
-
-	if (putenv(env) == 0) {
-	    RETURN(self);
-	}
-
-	if (valueSize > 0) {
-	    /* could not register, free */
-	    free(env);
-	}
+        if (aString == nil) {
+            /* env used only temporary for deregistration */
+            valueSize = 0;
+            env = __stringVal(aKeyStringOrSymbol);
+        } else if (__isStringLike(aString)) {
+            /* have to use stable memory for env */
+            valueSize = __stringSize(aString);
+            env = (char *)malloc(__stringSize(aKeyStringOrSymbol) + valueSize + 2);
+            if (env == 0)
+                goto err;
+            strcpy(env, __stringVal(aKeyStringOrSymbol));
+            strcat(env, "=");
+            strncat(env, __stringVal(aString), valueSize);
+        } else
+            goto err;
+
+        if (putenv(env) == 0) {
+            RETURN(self);
+        }
+
+        if (valueSize > 0) {
+            /* could not register, free */
+            free(env);
+        }
 err:;
     }
 %}.
@@ -9259,42 +9260,42 @@
     char *__locale, *ret;
 
     if (categorySymbol == @symbol(LC_ALL)) {
-	__category = LC_ALL;
+        __category = LC_ALL;
     } else if (categorySymbol == @symbol(LC_COLLATE)) {
-	__category = LC_COLLATE;
+        __category = LC_COLLATE;
     } else if (categorySymbol == @symbol(LC_CTYPE)) {
-	__category = LC_CTYPE;
+        __category = LC_CTYPE;
     } else if (categorySymbol == @symbol(LC_MESSAGES)) {
-	__category = LC_MESSAGES;
+        __category = LC_MESSAGES;
     } else if (categorySymbol == @symbol(LC_MONETARY)) {
-	__category = LC_MONETARY;
+        __category = LC_MONETARY;
     } else if (categorySymbol == @symbol(LC_NUMERIC)) {
-	__category = LC_NUMERIC;
+        __category = LC_NUMERIC;
     } else if (categorySymbol == @symbol(LC_TIME)) {
-	__category = LC_TIME;
+        __category = LC_TIME;
     } else {
-	error = @symbol(argument1);
-	goto out;
+        error = @symbol(argument1);
+        goto out;
     }
 
     if (localeStringOrNil == nil) {
-	__locale = 0;
+        __locale = 0;
     } else if (__isStringLike(localeStringOrNil)){
-	__locale = __stringVal(localeStringOrNil);
+        __locale = __stringVal(localeStringOrNil);
     } else {
-	error = @symbol(argument1);
-	goto out;
+        error = @symbol(argument1);
+        goto out;
     }
 
     ret = setlocale(__category, __locale);
     if (ret) {
-	locale = __MKSTRING(ret);
+        locale = __MKSTRING(ret);
     }
 
 out:;
 %}.
     locale notNil ifTrue:[
-	^ locale.
+        ^ locale.
     ].
     ^ self primitiveFailed:error.
 
@@ -9432,25 +9433,25 @@
      (actually, on a mac, it comes utf8-mac encoded)."
 
     Codeset notNil ifTrue:[
-	encodedPathNameOrOutputLine notNil ifTrue:[
-	    [
-		"/ cg: I am not sure, why this shortcut.
-		"/ calling the decoder directly should be much faster
-		Codeset == #utf8 ifTrue:[
-		    ^ encodedPathNameOrOutputLine utf8Decoded.
-		].
-		"/ Codeset encoder might not yet be initialized, sigh...
-		CodesetEncoder isNil ifTrue:[
-		    self getCodesetEncoder
-		].
-		CodesetEncoder notNil ifTrue:[
-		    ^ CodesetEncoder decodeString: encodedPathNameOrOutputLine
-		].
-	    ] on:InvalidEncodingError do:[:ex|
-		"maybe there are old filenames in ISO8859-x,
-		 just keep them untranslated"
-	    ].
-	].
+        encodedPathNameOrOutputLine notNil ifTrue:[
+            [
+                "/ cg: I am not sure, why this shortcut.
+                "/ calling the decoder directly should be much faster
+                Codeset == #utf8 ifTrue:[
+                    ^ encodedPathNameOrOutputLine utf8Decoded.
+                ].
+                "/ Codeset encoder might not yet be initialized, sigh...
+                CodesetEncoder isNil ifTrue:[
+                    self getCodesetEncoder
+                ].
+                CodesetEncoder notNil ifTrue:[
+                    ^ CodesetEncoder decodeString: encodedPathNameOrOutputLine
+                ].
+            ] on:DecodingError do:[:ex|
+                "maybe there are old filenames in ISO8859-x,
+                 just keep them untranslated"
+            ].
+        ].
     ].
     ^ encodedPathNameOrOutputLine
 
@@ -9469,72 +9470,72 @@
 
     sysPath := super defaultSystemPath.
     places :=
-	#(
-	    '/usr/local/lib/stx'
-	    '/usr/local/lib/smalltalk'
-	    '/usr/local/lib/smalltalk-x'
-	    '/usr/lib/stx'
-	    '/usr/lib/smalltalk'
-	    '/usr/lib/smalltalk-x'
-	    '/lib/stx'
-	    '/lib/smalltalk'
-	    '/lib/smalltalk-x'
-	    '/opt/stx'
-	    '/opt/smalltalk'
-	    '/opt/smalltalk-x'
-	).
+        #(
+            '/usr/local/lib/stx'
+            '/usr/local/lib/smalltalk'
+            '/usr/local/lib/smalltalk-x'
+            '/usr/lib/stx'
+            '/usr/lib/smalltalk'
+            '/usr/lib/smalltalk-x'
+            '/lib/stx'
+            '/lib/smalltalk'
+            '/lib/smalltalk-x'
+            '/opt/stx'
+            '/opt/smalltalk'
+            '/opt/smalltalk-x'
+        ).
 
     self isOSXlike ifTrue:[
-	|pathOfSTX|
-
-	 places :=
-		{
-		    '/Library/Smalltalk' .
-		    '/Library/Smalltalk-x' .
-		    '~/Library/Smalltalk' .
-		    '~/Library/Smalltalk-x' .
-		} , places.
-
-	pathOfSTX := OperatingSystem pathOfSTXExecutable.
-	pathOfSTX notNil ifTrue:[
-	    places :=
-		{
-		    (pathOfSTX asFilename / '../Packages') name .
-		    (pathOfSTX asFilename / '../../Packages') name .
-		} , places.
-	]
+        |pathOfSTX|
+
+         places :=
+                {
+                    '/Library/Smalltalk' .
+                    '/Library/Smalltalk-x' .
+                    '~/Library/Smalltalk' .
+                    '~/Library/Smalltalk-x' .
+                } , places.
+
+        pathOfSTX := OperatingSystem pathOfSTXExecutable.
+        pathOfSTX notNil ifTrue:[
+            places :=
+                {
+                    (pathOfSTX asFilename / '../Packages') name .
+                    (pathOfSTX asFilename / '../../Packages') name .
+                } , places.
+        ]
     ].
     places do:[:dirName |
-	|dir vsnDir|
-
-	dir := dirName asFilename.
-	(dir isDirectory) ifTrue:[
-	    "/ try to guess a gnu-smalltalk; skip it
-	    (dir construct:'initialize.st') exists ifFalse:[
-		vsnDir := dir / vsnDirName.
-		vsnDir exists ifTrue:[
-		    "/ new style: look for a major.minor directory there
-		    sysPath add:vsnDir.
-		] ifFalse:[
-		    "/ old style: look for a RELEASE file there and check if it matches
-		    releaseFile := dir construct:'RELEASE'.
-		    releaseFile exists ifTrue:[
-			s := releaseFile readStreamOrNil.
-			s notNil ifTrue:[
-			    v := Integer readFrom:s onError:-1.
-			    s close.
-			    v == majorVersionNr ifTrue:[
-				sysPath add:dirName
-			    ] ifFalse:[
-				('UnixOperatingSystem [info]: ignore files in ' , dir pathName , ' (RELEASE mismatch)') infoPrintCR.
-			    ]
-			] ifFalse:[
-			    ('UnixOperatingSystem [info]: ignore files in ' , dir pathName , ' (RELEASE missing)') infoPrintCR.
-			]
-		    ]
-		]
-	    ]
-	]
+        |dir vsnDir|
+
+        dir := dirName asFilename.
+        (dir isDirectory) ifTrue:[
+            "/ try to guess a gnu-smalltalk; skip it
+            (dir construct:'initialize.st') exists ifFalse:[
+                vsnDir := dir / vsnDirName.
+                vsnDir exists ifTrue:[
+                    "/ new style: look for a major.minor directory there
+                    sysPath add:vsnDir.
+                ] ifFalse:[
+                    "/ old style: look for a RELEASE file there and check if it matches
+                    releaseFile := dir construct:'RELEASE'.
+                    releaseFile exists ifTrue:[
+                        s := releaseFile readStreamOrNil.
+                        s notNil ifTrue:[
+                            v := Integer readFrom:s onError:-1.
+                            s close.
+                            v == majorVersionNr ifTrue:[
+                                sysPath add:dirName
+                            ] ifFalse:[
+                                ('UnixOperatingSystem [info]: ignore files in ' , dir pathName , ' (RELEASE mismatch)') infoPrintCR.
+                            ]
+                        ] ifFalse:[
+                            ('UnixOperatingSystem [info]: ignore files in ' , dir pathName , ' (RELEASE missing)') infoPrintCR.
+                        ]
+                    ]
+                ]
+            ]
+        ]
     ].
     ^ sysPath
 
@@ -9550,20 +9551,25 @@
      (actually, on a mac, it has to be utf8-mac encoded)."
 
     Codeset notNil ifTrue:[
-	pathName notNil ifTrue:[
-	    "/ cg: I am not sure, why this shortcut.
-	    "/ calling the encoder directly should be much faster
-	    Codeset == #utf8 ifTrue:[
-		^ pathName utf8Encoded
-	    ].
-	    "/ Codeset encoder might not yet be initialized, sigh...
-	    CodesetEncoder isNil ifTrue:[
-		self getCodesetEncoder
-	    ].
-	    CodesetEncoder notNil ifTrue:[
-		^ CodesetEncoder encodeString: pathName.
-	    ].
-	].
+        pathName notNil ifTrue:[
+            [
+                "/ cg: I am not sure, why this shortcut.
+                "/ calling the encoder directly should be much faster
+                Codeset == #utf8 ifTrue:[
+                    ^ pathName utf8Encoded
+                ].
+                "/ Codeset encoder might not yet be initialized, sigh...
+                CodesetEncoder isNil ifTrue:[
+                    self getCodesetEncoder
+                ].
+                CodesetEncoder notNil ifTrue:[
+                    ^ CodesetEncoder encodeString: pathName.
+                ].
+            ] on:EncodingError do:[:ex|
+                "maybe there are old filenames in ISO8859-x,
+                 just keep them untranslated"
+            ].
+        ].
     ].
     ^ pathName
 
@@ -9586,15 +9592,15 @@
 
     entries := OrderedCollection new.
     ('/proc/mounts' asFilename) readingLinesDo:[:eachLine |
-	|items mountInfo|
-
-	items := eachLine asCollectionOfWords.
-	mountInfo := (MountInfo new
-	    mountPointPath:(items at:2)
-	    deviceOrRemotePath:(items at:1)
-	    fsType:(items at:3)
-	    attributeString:(items at:4)).
-	entries add:mountInfo
+        |items mountInfo|
+
+        items := eachLine asCollectionOfWords.
+        mountInfo := (MountInfo new
+            mountPointPath:(items at:2)
+            deviceOrRemotePath:(items at:1)
+            fsType:(items at:3)
+            attributeString:(items at:4)).
+        entries add:mountInfo
     ].
     ^ entries
 
@@ -9622,16 +9628,16 @@
 
     if (__isSmallInteger(addr)
      && __bothSmallInteger(flags, id)) {
-	shmaddr = (void *) __intVal(addr);
-	shmflg = __intVal(flags);
-	shmid = __intVal(id);
-
-	address = shmat(shmid, shmaddr, shmflg);
-	if (address != (void *)-1) {
-	    RETURN (__MKEXTERNALBYTES(addr));
-	}
-	@global(LastErrorNumber) = __mkSmallInteger(errno);
-	RETURN (nil);
+        shmaddr = (void *) __intVal(addr);
+        shmflg = __intVal(flags);
+        shmid = __intVal(id);
+
+        address = shmat(shmid, shmaddr, shmflg);
+        if (address != (void *)-1) {
+            RETURN (__MKEXTERNALBYTES(addr));
+        }
+        @global(LastErrorNumber) = __mkSmallInteger(errno);
+        RETURN (nil);
     }
 #endif
 %}.
@@ -9650,14 +9656,14 @@
     int rslt;
 
     if (__isSmallInteger(addr)) {
-	shmaddr = (void *) __intVal(addr);
-
-	rslt = shmdt(shmaddr);
-	if (rslt != -1) {
-	    RETURN (true);
-	}
-	@global(LastErrorNumber) = __mkSmallInteger(errno);
-	RETURN (false);
+        shmaddr = (void *) __intVal(addr);
+
+        rslt = shmdt(shmaddr);
+        if (rslt != -1) {
+            RETURN (true);
+        }
+        @global(LastErrorNumber) = __mkSmallInteger(errno);
+        RETURN (false);
     }
 #endif
 %}.
@@ -9675,14 +9681,14 @@
 #ifdef WANT_SHM
     if (__bothSmallInteger(key, size)
      && __isSmallInteger(flags)) {
-	int rslt;
-
-	rslt = shmget(__intVal(key), __intVal(size), __intVal(flags));
-	if (rslt != -1) {
-	    RETURN (__mkSmallInteger(rslt));
-	}
-	@global(LastErrorNumber) = __mkSmallInteger(errno);
-	RETURN (nil);
+        int rslt;
+
+        rslt = shmget(__intVal(key), __intVal(size), __intVal(flags));
+        if (rslt != -1) {
+            RETURN (__mkSmallInteger(rslt));
+        }
+        @global(LastErrorNumber) = __mkSmallInteger(errno);
+        RETURN (nil);
     }
 #endif
 %}.
@@ -9727,67 +9733,67 @@
     if (__bothSmallInteger(y, m)
      && __bothSmallInteger(d, h)
      && __bothSmallInteger(min, s)) {
-	tm.tm_hour = __intVal(h);
-	tm.tm_min = __intVal(min);
-	tm.tm_sec = __intVal(s);
-
-	tm.tm_year = __intVal(y) - 1900;
-	tm.tm_mon = __intVal(m) - 1;
-	tm.tm_mday = __intVal(d);
-	tm.tm_isdst = -1;
+        tm.tm_hour = __intVal(h);
+        tm.tm_min = __intVal(min);
+        tm.tm_sec = __intVal(s);
+
+        tm.tm_year = __intVal(y) - 1900;
+        tm.tm_mon = __intVal(m) - 1;
+        tm.tm_mday = __intVal(d);
+        tm.tm_isdst = -1;
 
 #ifndef HAS_MKTIME64
-	if (__intVal(y) > 2038) goto outOfRange;
-	if (__intVal(y) == 2038) {
-	    if (__intVal(m) > 1) goto outOfRange;
-	    if (__intVal(d) > 19) goto outOfRange;
-	    if (__intVal(d) == 19) {
-		if (__intVal(h) > 3) goto outOfRange;
-		if (__intVal(h) == 3) {
-		    if (__intVal(min) > 14) goto outOfRange;
-		    if (__intVal(min) == 14) {
-			if (__intVal(s) > 7) goto outOfRange;
-		    }
-		}
-	    }
-	}
+        if (__intVal(y) > 2038) goto outOfRange;
+        if (__intVal(y) == 2038) {
+            if (__intVal(m) > 1) goto outOfRange;
+            if (__intVal(d) > 19) goto outOfRange;
+            if (__intVal(d) == 19) {
+                if (__intVal(h) > 3) goto outOfRange;
+                if (__intVal(h) == 3) {
+                    if (__intVal(min) > 14) goto outOfRange;
+                    if (__intVal(min) == 14) {
+                        if (__intVal(s) > 7) goto outOfRange;
+                    }
+                }
+            }
+        }
 #endif
 
 #ifdef HAS_TIMEGM
-	if (utcBoolean == true) {               /* convert to utc time */
+        if (utcBoolean == true) {               /* convert to utc time */
 # ifdef HAS_MKTIME64
-	    t = timegm64(&tm);                  /* timegm() interprets tm as utc time */
+            t = timegm64(&tm);                  /* timegm() interprets tm as utc time */
 # else
-	    t = timegm(&tm);                    /* timegm() interprets tm as utc time */
-# endif
-	} else
-#endif
-	{
+            t = timegm(&tm);                    /* timegm() interprets tm as utc time */
+# endif
+        } else
+#endif
+        {
 #ifdef HAS_MKTIME64
-	    t = mktime64(&tm);                  /* mktime() interprets tm as localtime */
+            t = mktime64(&tm);                  /* mktime() interprets tm as localtime */
 #else
-	    t = mktime(&tm);                    /* mktime() interprets tm as localtime */
-#endif
-	}
-	if (t != (TIME_T)-1) {
+            t = mktime(&tm);                    /* mktime() interprets tm as localtime */
+#endif
+        }
+        if (t != (TIME_T)-1) {
 #ifndef HAS_TIMEGM
-	    if (utcBoolean == true) {           /* convert to utc time */
-		// printf("tz=%d\n", TIMEZONE(&tm));
-		t = t - TIMEZONE(&tm);          /* TIMZONE = seconds westward from 0 */
-	    }
+            if (utcBoolean == true) {           /* convert to utc time */
+                // printf("tz=%d\n", TIMEZONE(&tm));
+                t = t - TIMEZONE(&tm);          /* TIMZONE = seconds westward from 0 */
+            }
 #endif
 #ifdef HAS_MKTIME64
-	    osSeconds = __MKLARGEINT64(1, (t & 0xFFFFFFFF), (t>>32)& 0xFFFFFFFF);
+            osSeconds = __MKLARGEINT64(1, (t & 0xFFFFFFFF), (t>>32)& 0xFFFFFFFF);
 #else
-	    /* be careful, t can be negative at the start of the epoch ! */
-	    osSeconds = __MKINT((INT)t);
-#endif
-	}
+            /* be careful, t can be negative at the start of the epoch ! */
+            osSeconds = __MKINT((INT)t);
+#endif
+        }
     }
   outOfRange: ;
 %}.
     osSeconds notNil ifTrue:[
-	^ osSeconds * 1000 + millis
+        ^ osSeconds * 1000 + millis
     ].
     ^ TimeConversionError raiseRequest.
 
@@ -9820,9 +9826,9 @@
 %{
 #ifdef __SCHTEAM__
     {
-	long nanos = java.lang.System.nanoTime();
-
-	return context._RETURN( STInteger._new(nanos / 1000) );
+        long nanos = java.lang.System.nanoTime();
+
+        return context._RETURN( STInteger._new(nanos / 1000) );
     }
     /* NOTREACHED */
 #else
@@ -9833,17 +9839,17 @@
     static int has_clock_gettime = 1;
 
     if (has_clock_gettime) {
-	if (clock_gettime(CLOCK_MONOTONIC, &ts) != -1) {
-	    _secs = ts.tv_sec;
-	    _micros  = ts.tv_nsec / 1000;
-	    goto out;
-	} else {
-	    /*
-	     * clock_gettime is not implemented in the kernel
-	     * fall through to alternative implementation
-	     */
-	    has_clock_gettime = 0;
-	}
+        if (clock_gettime(CLOCK_MONOTONIC, &ts) != -1) {
+            _secs = ts.tv_sec;
+            _micros  = ts.tv_nsec / 1000;
+            goto out;
+        } else {
+            /*
+             * clock_gettime is not implemented in the kernel
+             * fall through to alternative implementation
+             */
+            has_clock_gettime = 0;
+        }
     }
 # endif
 
@@ -9852,8 +9858,8 @@
 
     gettimeofday(&tb, NULL /* &tzb */);
     if (tb.tv_usec >= (1000000)) {
-	error = @symbol(bad);
-	goto err;
+        error = @symbol(bad);
+        goto err;
     }
 
     _secs = tb.tv_sec;
@@ -9864,18 +9870,18 @@
 
 # if __POINTER_SIZE__ == 8
     {
-	unsigned INT rslt;
-
-	rslt = (unsigned INT)_secs * 1000000 + _micros;
-	RETURN (__MKUINT(rslt));
+        unsigned INT rslt;
+
+        rslt = (unsigned INT)_secs * 1000000 + _micros;
+        RETURN (__MKUINT(rslt));
     }
 # else
 #  ifdef HAS_LONGLONG
     {
-	unsigned long long rslt;
-
-	rslt = (unsigned long long)_secs * 1000000 + _micros;
-	RETURN (__MKLARGEINT64(1, (unsigned INT)(rslt & 0xFFFFFFFF), (unsigned INT)(rslt >> 32)));
+        unsigned long long rslt;
+
+        rslt = (unsigned long long)_secs * 1000000 + _micros;
+        RETURN (__MKLARGEINT64(1, (unsigned INT)(rslt & 0xFFFFFFFF), (unsigned INT)(rslt >> 32)));
     }
 #  else
     seconds = __MKUINT(_secs);
@@ -9887,10 +9893,10 @@
 %}.
 
     seconds notNil ifTrue:[
-	^ (seconds * 1000000) + micros
+        ^ (seconds * 1000000) + micros
     ].
     error isNil ifTrue:[
-	^ self getMillisecondTime * 1000
+        ^ self getMillisecondTime * 1000
     ].
     self primitiveFailed:error.
 
@@ -9909,8 +9915,8 @@
      Use the XXXmillisecondTime:-methods to compare and add time deltas - these know about the wrap.
 
      BAD DESIGN:
-	This should be changed to return some instance of RelativeTime,
-	and these computations moved there.
+        This should be changed to return some instance of RelativeTime,
+        and these computations moved there.
 
      Don't use this method in application code since it is an internal (private)
      interface. For compatibility with ST-80, use Time millisecondClockValue.
@@ -9919,8 +9925,8 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     {
-	long millis = java.lang.System.currentTimeMillis();
-	return context._RETURN( STInteger._new(millis) );
+        long millis = java.lang.System.currentTimeMillis();
+        return context._RETURN( STInteger._new(millis) );
     }
     /* NOTREACHED */
 #else
@@ -9931,16 +9937,16 @@
     struct timespec ts;
 
     if (has_clock_gettime) {
-	if (clock_gettime(CLOCK_MONOTONIC, &ts) != -1) {
-	    t = ts.tv_sec*1000 + ts.tv_nsec/1000000;
-	    goto out;
-	} else {
-	    /*
-	     * clock_gettime is not implemented in the kernel
-	     * fall through to alternative implementation
-	     */
-	    has_clock_gettime = 0;
-	}
+        if (clock_gettime(CLOCK_MONOTONIC, &ts) != -1) {
+            t = ts.tv_sec*1000 + ts.tv_nsec/1000000;
+            goto out;
+        } else {
+            /*
+             * clock_gettime is not implemented in the kernel
+             * fall through to alternative implementation
+             */
+            has_clock_gettime = 0;
+        }
     }
 # endif /*  _POSIX_MONOTONIC_CLOCK */
 
@@ -9956,12 +9962,12 @@
     struct tms tb;
 
     if (!millisecondsPerTick) {
-	int ticksPerSecond = sysconf(_SC_CLK_TCK);
-	if (ticksPerSecond <= 0)
-	    goto err;
-	if (ticksPerSecond > 1000)
-	    goto err;
-	millisecondsPerTick = 1000 / ticksPerSecond;
+        int ticksPerSecond = sysconf(_SC_CLK_TCK);
+        if (ticksPerSecond <= 0)
+            goto err;
+        if (ticksPerSecond > 1000)
+            goto err;
+        millisecondsPerTick = 1000 / ticksPerSecond;
 /*
 printf("milliSecondsPerTick: %d\n", millisecondsPerTick);
 */
@@ -9969,7 +9975,7 @@
 
     ticks = times(&tb);
     if (ticks == -1)
-	goto err;
+        goto err;
 
     t = ticks * millisecondsPerTick;
 
@@ -10019,8 +10025,8 @@
 %{
 #ifdef __SCHTEAM__
     {
-	long millisSince1970 = java.lang.System.currentTimeMillis();
-	return context._RETURN( STInteger._new(millisSince1970));
+        long millisSince1970 = java.lang.System.currentTimeMillis();
+        return context._RETURN( STInteger._new(millisSince1970));
     }
     /* NOTREACHED */
 #else
@@ -10029,11 +10035,11 @@
 # if !defined(HAS_GETTIMEOFDAY)
 #  if defined(HAS_FTIME)
     {
-	struct timeb timebuffer;
-
-	ftime(&timebuffer);
-	_secs = timebuffer.time;
-	_millis = timebuffer.millitm;
+        struct timeb timebuffer;
+
+        ftime(&timebuffer);
+        _secs = timebuffer.time;
+        _millis = timebuffer.millitm;
     }
 #    define HAVE_TIME
 #  endif /* HAS_FTIME */
@@ -10046,33 +10052,33 @@
      */
 
     {
-	/*
-	 * bsd time
-	 */
-	struct timeval tb;
-	/* struct timezone tzb; */
-
-	gettimeofday(&tb, NULL /* &tzb */);
-
-	_secs = tb.tv_sec;
-	_millis = tb.tv_usec / 1000;
+        /*
+         * bsd time
+         */
+        struct timeval tb;
+        /* struct timezone tzb; */
+
+        gettimeofday(&tb, NULL /* &tzb */);
+
+        _secs = tb.tv_sec;
+        _millis = tb.tv_usec / 1000;
     }
 # endif
 
 # if __POINTER_SIZE__ == 8
     {
-	unsigned INT rslt;
-
-	rslt = (unsigned INT)_secs * 1000 + _millis;
-	RETURN (__MKUINT(rslt));
+        unsigned INT rslt;
+
+        rslt = (unsigned INT)_secs * 1000 + _millis;
+        RETURN (__MKUINT(rslt));
     }
 # else
 #  ifdef HAS_LONGLONG
     {
-	unsigned long long rslt;
-
-	rslt = (unsigned long long)_secs * 1000 + _millis;
-	RETURN (__MKLARGEINT64(1, (unsigned INT)(rslt & 0xFFFFFFFF), (unsigned INT)(rslt >> 32)));
+        unsigned long long rslt;
+
+        rslt = (unsigned long long)_secs * 1000 + _millis;
+        RETURN (__MKLARGEINT64(1, (unsigned INT)(rslt & 0xFFFFFFFF), (unsigned INT)(rslt >> 32)));
     }
 #  else
     seconds = __MKUINT(_secs);
@@ -10082,7 +10088,7 @@
 #endif /* SCHTEAM */
 %}.
     seconds notNil ifTrue:[
-	^ (seconds * 1000) + millis
+        ^ (seconds * 1000) + millis
     ].
 
     self primitiveFailed.
@@ -10147,8 +10153,8 @@
 %{  /* NOCONTEXT */
 
     if (__isSmallInteger(numberOfSeconds)) {
-	sleep(__intVal(numberOfSeconds));
-	RETURN ( self );
+        sleep(__intVal(numberOfSeconds));
+        RETURN ( self );
     }
 %}.
     "
@@ -10173,104 +10179,104 @@
 #ifdef __SCHTEAM__
     if (osSeconds.isSmallInteger()
      && osMilliseconds.isSmallInteger()) {
-	long _seconds = osSeconds.longValue();
-	long _millis = osMilliseconds.longValue();
-	long _millisSinceEpoch = _seconds * 1000 + _millis;
-	java.util.TimeZone _tz;
-	java.util.Calendar _calendar;
-	int _wDay;
-
-	if (isLocalTime == STObject.True) {
-	    _tz = java.util.TimeZone.getDefault();
-	} else {
-	    _tz = java.util.TimeZone.getTimeZone("UTC");
-	}
-	_calendar = java.util.Calendar.getInstance(_tz);
-	_calendar.setTimeInMillis(_millisSinceEpoch);
-
-	year = STInteger._new( _calendar.get(java.util.Calendar.YEAR) );
-	month = STInteger._new( _calendar.get(java.util.Calendar.MONTH) + 1 );
-	day = STInteger._new( _calendar.get(java.util.Calendar.DAY_OF_MONTH) );
-	hours = STInteger._new( _calendar.get(java.util.Calendar.HOUR_OF_DAY) );
-	minutes = STInteger._new( _calendar.get(java.util.Calendar.MINUTE) );
-	seconds = STInteger._new( _calendar.get(java.util.Calendar.SECOND) );
-	yDay = STInteger._new( _calendar.get(java.util.Calendar.DAY_OF_YEAR) );
-	_wDay = _calendar.get(java.util.Calendar.DAY_OF_WEEK);
-	// convert from 1=SUN, 2=MON,...
-	// to 1=MON, 2=TUE,...
-	_wDay = _wDay - 1; if (_wDay < 1) _wDay += 7;
-	wDay = STInteger._new( _wDay );
-	utcOffset = STInteger._new( (_calendar.get(java.util.Calendar.ZONE_OFFSET)) / 1000 );
-	dstOffset = STInteger._new( (_calendar.get(java.util.Calendar.DST_OFFSET)) / 1000 );
+        long _seconds = osSeconds.longValue();
+        long _millis = osMilliseconds.longValue();
+        long _millisSinceEpoch = _seconds * 1000 + _millis;
+        java.util.TimeZone _tz;
+        java.util.Calendar _calendar;
+        int _wDay;
+
+        if (isLocalTime == STObject.True) {
+            _tz = java.util.TimeZone.getDefault();
+        } else {
+            _tz = java.util.TimeZone.getTimeZone("UTC");
+        }
+        _calendar = java.util.Calendar.getInstance(_tz);
+        _calendar.setTimeInMillis(_millisSinceEpoch);
+
+        year = STInteger._new( _calendar.get(java.util.Calendar.YEAR) );
+        month = STInteger._new( _calendar.get(java.util.Calendar.MONTH) + 1 );
+        day = STInteger._new( _calendar.get(java.util.Calendar.DAY_OF_MONTH) );
+        hours = STInteger._new( _calendar.get(java.util.Calendar.HOUR_OF_DAY) );
+        minutes = STInteger._new( _calendar.get(java.util.Calendar.MINUTE) );
+        seconds = STInteger._new( _calendar.get(java.util.Calendar.SECOND) );
+        yDay = STInteger._new( _calendar.get(java.util.Calendar.DAY_OF_YEAR) );
+        _wDay = _calendar.get(java.util.Calendar.DAY_OF_WEEK);
+        // convert from 1=SUN, 2=MON,...
+        // to 1=MON, 2=TUE,...
+        _wDay = _wDay - 1; if (_wDay < 1) _wDay += 7;
+        wDay = STInteger._new( _wDay );
+        utcOffset = STInteger._new( (_calendar.get(java.util.Calendar.ZONE_OFFSET)) / 1000 );
+        dstOffset = STInteger._new( (_calendar.get(java.util.Calendar.DST_OFFSET)) / 1000 );
     }
 #else
     struct tm tmValue, *result;
     time_t tt = __signedLongIntVal(osSeconds);
 
     if (tt == 0 && !__isSmallInteger(osSeconds))
-	goto out;             // __singedLongIntVal() returns 0 on failure
+        goto out;             // __singedLongIntVal() returns 0 on failure
 
     /* try cache */
     {
-	OBJ lastSeconds = @global(LastTimeInfoSeconds);
-
-	if (__isInteger(lastSeconds)
-	     && (__signedLongIntVal(lastSeconds) == tt)
-	     && (@global(LastTimeInfoIsLocal) == isLocalTime)
-	) {
-	    OBJ lastTimeInfo = @global(LastTimeInfo);
-	    if (lastTimeInfo != nil) {
-		info = lastTimeInfo;
-		goto out;
-	    }
-	}
+        OBJ lastSeconds = @global(LastTimeInfoSeconds);
+
+        if (__isInteger(lastSeconds)
+             && (__signedLongIntVal(lastSeconds) == tt)
+             && (@global(LastTimeInfoIsLocal) == isLocalTime)
+        ) {
+            OBJ lastTimeInfo = @global(LastTimeInfo);
+            if (lastTimeInfo != nil) {
+                info = lastTimeInfo;
+                goto out;
+            }
+        }
     }
 
     result = (isLocalTime == true) ? localtime_r(&tt, &tmValue) :  gmtime_r(&tt, &tmValue);
     if (result != NULL) {
-	hours = __mkSmallInteger(tmValue.tm_hour);
-	minutes = __mkSmallInteger(tmValue.tm_min);
-	seconds = __mkSmallInteger(tmValue.tm_sec);
-
-	year = __mkSmallInteger(tmValue.tm_year + 1900);
-	month = __mkSmallInteger(tmValue.tm_mon + 1);
-	day = __mkSmallInteger(tmValue.tm_mday);
-
-	yDay = __mkSmallInteger(tmValue.tm_yday+1);
-	wDay = __mkSmallInteger(tmValue.tm_wday == 0 ? 7 : tmValue.tm_wday);
-	utcOffset = __mkSmallInteger(TIMEZONE(&tmValue));
-	dst = (tmValue.tm_isdst == 0 ? false : true);
+        hours = __mkSmallInteger(tmValue.tm_hour);
+        minutes = __mkSmallInteger(tmValue.tm_min);
+        seconds = __mkSmallInteger(tmValue.tm_sec);
+
+        year = __mkSmallInteger(tmValue.tm_year + 1900);
+        month = __mkSmallInteger(tmValue.tm_mon + 1);
+        day = __mkSmallInteger(tmValue.tm_mday);
+
+        yDay = __mkSmallInteger(tmValue.tm_yday+1);
+        wDay = __mkSmallInteger(tmValue.tm_wday == 0 ? 7 : tmValue.tm_wday);
+        utcOffset = __mkSmallInteger(TIMEZONE(&tmValue));
+        dst = (tmValue.tm_isdst == 0 ? false : true);
     }
 out:;
 #endif
 %}.
     info notNil ifTrue:[
-	"there is a matching cached value"
-	LastTimeInfoMilliseconds == osMilliseconds ifTrue:[
-	    ^ info.
-	].
-	info := info copy.
-	info milliseconds:osMilliseconds.
+        "there is a matching cached value"
+        LastTimeInfoMilliseconds == osMilliseconds ifTrue:[
+            ^ info.
+        ].
+        info := info copy.
+        info milliseconds:osMilliseconds.
     ] ifFalse:[
-	year isNil ifTrue:[
-	    TimeConversionError raiseErrorString:' - out of range'.
-	].
-	dst isNil ifTrue:[
-	    dst := (dstOffset ~= 0)
-	].
-	info := self timeInfoClass new.
-	info
-	    year:year
-	    month:month
-	    day:day
-	    hours:hours
-	    minutes:minutes
-	    seconds:seconds
-	    milliseconds:osMilliseconds
-	    utcOffset:utcOffset
-	    dst:dst
-	    dayInYear:yDay
-	    dayInWeek:wDay.
+        year isNil ifTrue:[
+            TimeConversionError raiseErrorString:' - out of range'.
+        ].
+        dst isNil ifTrue:[
+            dst := (dstOffset ~= 0)
+        ].
+        info := self timeInfoClass new.
+        info
+            year:year
+            month:month
+            day:day
+            hours:hours
+            minutes:minutes
+            seconds:seconds
+            milliseconds:osMilliseconds
+            utcOffset:utcOffset
+            dst:dst
+            dayInYear:yDay
+            dayInWeek:wDay.
     ].
 
 %{
@@ -10367,11 +10373,11 @@
     info := self userInfoOf:userID.
     (info notNil
     and:[info includesKey:#gecos]) ifTrue:[
-	gecos := info at:#gecos.
-	(gecos includes:$,) ifTrue:[
-	    ^ gecos copyTo:(gecos indexOf:$,) - 1
-	].
-	^ gecos
+        gecos := info at:#gecos.
+        (gecos includes:$,) ifTrue:[
+            ^ gecos copyTo:(gecos indexOf:$,) - 1
+        ].
+        ^ gecos
     ].
     ^ self getUserNameFromID:userID
 
@@ -10410,10 +10416,10 @@
     struct group *g;
 
     if (__isSmallInteger(aNumber)) {
-	g = getgrgid(__intVal(aNumber));
-	if (g) {
-	    RETURN ( __MKSTRING(g->gr_name) );
-	}
+        g = getgrgid(__intVal(aNumber));
+        if (g) {
+            RETURN ( __MKSTRING(g->gr_name) );
+        }
     }
 %}.
     ^ '???'
@@ -10433,10 +10439,10 @@
 
     homeDir := self getEnvironment:'HOME'.
     homeDir isNil ifTrue:[
-	"/ mhmh - can only happen if started via some uncorrectly
-	"/ initialized subprocess...
-	'UnixOperatingSystem [warning]: cannot figure out home directory' errorPrintCR.
-	homeDir := '/tmp'.
+        "/ mhmh - can only happen if started via some uncorrectly
+        "/ initialized subprocess...
+        'UnixOperatingSystem [warning]: cannot figure out home directory' errorPrintCR.
+        homeDir := '/tmp'.
     ].
     ^ self decodePath:homeDir
 
@@ -10461,32 +10467,32 @@
     char *name = (char *)0;
 
     if (firstCall) {
-	/*
-	 * try a few common environment variables ...
-	 */
-	name = getenv("LOGNAME");
-	if (! name || (name[0] == 0)) {
-	    name = getlogin();
-	    if (! name || (name[0] == 0) ) {
-		name = getenv("LOGIN");
-		if (! name || (name[0] == 0) ) {
-		    name = getenv("USER");
-		}
-	    }
-	}
-	if (name && (strlen(name) < sizeof(cachedName))) {
-	    strcpy(cachedName, name);
-	    firstCall = 0;
-	}
+        /*
+         * try a few common environment variables ...
+         */
+        name = getenv("LOGNAME");
+        if (! name || (name[0] == 0)) {
+            name = getlogin();
+            if (! name || (name[0] == 0) ) {
+                name = getenv("LOGIN");
+                if (! name || (name[0] == 0) ) {
+                    name = getenv("USER");
+                }
+            }
+        }
+        if (name && (strlen(name) < sizeof(cachedName))) {
+            strcpy(cachedName, name);
+            firstCall = 0;
+        }
     } else {
-	name = cachedName;
+        name = cachedName;
     }
 
     /*
      * nope - I really dont know who you are.
      */
     if (! name || (name[0] == 0) ) {
-	name = "you";
+        name = "you";
     }
 
     RETURN ( __MKSTRING(name) );
@@ -10523,15 +10529,15 @@
     struct passwd *p;
 
     if (__isSmallInteger(aNumber)) {
-	p = getpwuid(__intVal(aNumber));
-	if (p) {
-	    RETURN ( __MKSTRING(p->pw_name) );
-	}
+        p = getpwuid(__intVal(aNumber));
+        if (p) {
+            RETURN ( __MKSTRING(p->pw_name) );
+        }
     }
 #endif /* unix-like */
 %}.
     aNumber == self getUserID ifTrue:[
-	^ self getLoginName
+        ^ self getLoginName
     ].
 
     ^ '? (' , aNumber printString , ')'
@@ -10587,68 +10593,68 @@
     struct passwd pwd;
 
     if (__isStringLike(aNameOrID)) {
-	getpwnam_r(__stringVal(aNameOrID), &pwd, buf, sizeof(buf), &result);
+        getpwnam_r(__stringVal(aNameOrID), &pwd, buf, sizeof(buf), &result);
     } else if (__isSmallInteger(aNameOrID)) {
-	getpwuid_r(__intVal(aNameOrID), &pwd, buf, sizeof(buf), &result);
+        getpwuid_r(__intVal(aNameOrID), &pwd, buf, sizeof(buf), &result);
     }
 #else
     if (__isStringLike(aNameOrID)) {
-	result = getpwnam(__stringVal(aNameOrID));
+        result = getpwnam(__stringVal(aNameOrID));
     } else if (__isSmallInteger(aNameOrID)) {
-	result = getpwuid(__intVal(aNameOrID));
+        result = getpwuid(__intVal(aNameOrID));
     }
 #endif /* ! _POSIX_SOURCE */
 
     if (result) {
-	returnArray = __ARRAY_NEW_INT(20);
-	__PROTECT__(returnArray);
-	tmp = __MKSTRING(result->pw_name);
-	__UNPROTECT__(returnArray);
-	__arrayVal(returnArray)[idx++] = @symbol(name);
-	__arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
+        returnArray = __ARRAY_NEW_INT(20);
+        __PROTECT__(returnArray);
+        tmp = __MKSTRING(result->pw_name);
+        __UNPROTECT__(returnArray);
+        __arrayVal(returnArray)[idx++] = @symbol(name);
+        __arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
 #  ifndef NO_PWD_PASSWD
-	__PROTECT__(returnArray);
-	tmp = __MKSTRING(result->pw_passwd);
-	__UNPROTECT__(returnArray);
-	__arrayVal(returnArray)[idx++] = @symbol(passwd);
-	__arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
+        __PROTECT__(returnArray);
+        tmp = __MKSTRING(result->pw_passwd);
+        __UNPROTECT__(returnArray);
+        __arrayVal(returnArray)[idx++] = @symbol(passwd);
+        __arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
 #  endif
 #  ifdef SYSV4
-	__PROTECT__(returnArray);
-	tmp = __MKSTRING(result->pw_age);
-	__UNPROTECT__(returnArray);
-	__arrayVal(returnArray)[idx++] = @symbol(age);
-	__arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
-	__PROTECT__(returnArray);
-	tmp = __MKSTRING(result->pw_comment);
-	__UNPROTECT__(returnArray);
-	__arrayVal(returnArray)[idx++] = @symbol(comment);
-	__arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
-#  endif
-	__PROTECT__(returnArray);
-	tmp = __MKSTRING(result->pw_dir);
-	__UNPROTECT__(returnArray);
-	__arrayVal(returnArray)[idx++] = @symbol(dir);
-	__arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
+        __PROTECT__(returnArray);
+        tmp = __MKSTRING(result->pw_age);
+        __UNPROTECT__(returnArray);
+        __arrayVal(returnArray)[idx++] = @symbol(age);
+        __arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
+        __PROTECT__(returnArray);
+        tmp = __MKSTRING(result->pw_comment);
+        __UNPROTECT__(returnArray);
+        __arrayVal(returnArray)[idx++] = @symbol(comment);
+        __arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
+#  endif
+        __PROTECT__(returnArray);
+        tmp = __MKSTRING(result->pw_dir);
+        __UNPROTECT__(returnArray);
+        __arrayVal(returnArray)[idx++] = @symbol(dir);
+        __arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
 #  ifndef NO_PWD_GECOS
-	__PROTECT__(returnArray);
-	tmp = __MKSTRING(result->pw_gecos);
-	__UNPROTECT__(returnArray);
-	__arrayVal(returnArray)[idx++] = @symbol(gecos);
-	__arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
-#  endif
-	__PROTECT__(returnArray);
-	tmp = __MKSTRING(result->pw_shell);
-	 __UNPROTECT__(returnArray);
-	__arrayVal(returnArray)[idx++] = @symbol(shell);
-	__arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
-
-	__arrayVal(returnArray)[idx++] = @symbol(uid);
-	__arrayVal(returnArray)[idx++] = __mkSmallInteger(result->pw_uid);
-
-	__arrayVal(returnArray)[idx++] = @symbol(gid);
-	__arrayVal(returnArray)[idx++] = __mkSmallInteger(result->pw_gid);
-	RETURN(returnArray);
+        __PROTECT__(returnArray);
+        tmp = __MKSTRING(result->pw_gecos);
+        __UNPROTECT__(returnArray);
+        __arrayVal(returnArray)[idx++] = @symbol(gecos);
+        __arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
+#  endif
+        __PROTECT__(returnArray);
+        tmp = __MKSTRING(result->pw_shell);
+         __UNPROTECT__(returnArray);
+        __arrayVal(returnArray)[idx++] = @symbol(shell);
+        __arrayVal(returnArray)[idx++] = tmp; __STORE(returnArray, tmp);
+
+        __arrayVal(returnArray)[idx++] = @symbol(uid);
+        __arrayVal(returnArray)[idx++] = __mkSmallInteger(result->pw_uid);
+
+        __arrayVal(returnArray)[idx++] = @symbol(gid);
+        __arrayVal(returnArray)[idx++] = __mkSmallInteger(result->pw_gid);
+        RETURN(returnArray);
     }
 # endif /* ! NO_PWD */
 %}.
@@ -10683,22 +10689,22 @@
     info := IdentityDictionary new.
 
     infoArray notNil ifTrue:[
-	infoArray pairWiseDo:[:key :value|
-	    key notNil ifTrue:[
-		info at:key put:value.
-		key == #name ifTrue:[name := value].
-		key == #dir  ifTrue:[dir := value].
-	    ].
-	].
+        infoArray pairWiseDo:[:key :value|
+            key notNil ifTrue:[
+                info at:key put:value.
+                key == #name ifTrue:[name := value].
+                key == #dir  ifTrue:[dir := value].
+            ].
+        ].
     ].
 
     name isNil ifTrue:[
-	info at:#name put:#unknown
+        info at:#name put:#unknown
     ].
     dir isNil ifTrue:[
-	aNameOrID == self getUserID ifTrue:[
-	    info at:#dir put:self getHomeDirectory
-	]
+        aNameOrID == self getUserID ifTrue:[
+            info at:#dir put:self getHomeDirectory
+        ]
     ].
 
     ^ info
@@ -10760,11 +10766,11 @@
 #   define __BLOCKING_WAIT__ 1
 
     if (blocking != true) {
-	/*
-	 * We do not support nonBlocking waits, so signal an error
-	 * Sorry about the goto, but with all these ifdefs ...
-	 */
-	goto done;
+        /*
+         * We do not support nonBlocking waits, so signal an error
+         * Sorry about the goto, but with all these ifdefs ...
+         */
+        goto done;
     }
 # endif /*!HAS_WAIT3*/
 #endif  /*!HAS_WAITPID*/
@@ -10795,7 +10801,7 @@
 #endif
 
     do {
-	p = __WAIT;
+        p = __WAIT;
     } while (p == -1 && errno == EINTR);
 
 #if __BLOCKING_WAIT__
@@ -10806,35 +10812,35 @@
 #undef __WAIT
 
     if (p == 0)
-	RETURN(nil)
+        RETURN(nil)
 
     if (p == -1) {
-	if (errno == ECHILD)
-	    RETURN(nil);
+        if (errno == ECHILD)
+            RETURN(nil);
     } else {
-	pid = __mkSmallInteger(p);
-	if (WIFEXITED(s)) {
-	    status = @symbol(exit);
-	    code = __mkSmallInteger(WEXITSTATUS(s));
-	    core = WCOREDUMP(s) ? true : false;
-	} else if (WIFSIGNALED(s)) {
-	    status = @symbol(signal);
-	    code = __mkSmallInteger(WTERMSIG(s));
-	} else if (WIFSTOPPED(s)) {
-	    status = @symbol(stop);
-	    code = __mkSmallInteger(WSTOPSIG(s));
-	}
+        pid = __mkSmallInteger(p);
+        if (WIFEXITED(s)) {
+            status = @symbol(exit);
+            code = __mkSmallInteger(WEXITSTATUS(s));
+            core = WCOREDUMP(s) ? true : false;
+        } else if (WIFSIGNALED(s)) {
+            status = @symbol(signal);
+            code = __mkSmallInteger(WTERMSIG(s));
+        } else if (WIFSTOPPED(s)) {
+            status = @symbol(stop);
+            code = __mkSmallInteger(WSTOPSIG(s));
+        }
 #if defined(WIFCONTINUED)
-	else if (WIFCONTINUED(s)) {
-	    status = @symbol(continue);
-	}
+        else if (WIFCONTINUED(s)) {
+            status = @symbol(continue);
+        }
 #endif
     }
 done: ;
 %}.
 
     (status isNil or:[pid isNil]) ifTrue:[
-	^ self primitiveFailed
+        ^ self primitiveFailed
     ].
 
 "/ Transcript show:'pid: '; show:pid; show:' status: '; show:status;
@@ -10873,10 +10879,10 @@
 # endif
 # if defined(DELAY_FLAG)
     if (__isSmallInteger(fd)) {
-	int f = __intVal(fd);
-
-	flags = fcntl(f, F_GETFL, 0);
-	RETURN ((flags & DELAY_FLAG) ? false : true );
+        int f = __intVal(fd);
+
+        flags = fcntl(f, F_GETFL, 0);
+        RETURN ((flags & DELAY_FLAG) ? false : true );
     }
 #  undef DELAY_FLAG
 # endif
@@ -10897,13 +10903,13 @@
      */
 # if 0 && defined(FIONREAD)
     {
-	int n;
-
-	if (__isSmallInteger(fd)) {
-	    if (ioctl(__intVal(fd), FIONREAD, &n) >= 0) {
-		RETURN (__MKINT(n));
-	    }
-	}
+        int n;
+
+        if (__isSmallInteger(fd)) {
+            if (ioctl(__intVal(fd), FIONREAD, &n) >= 0) {
+                RETURN (__MKINT(n));
+            }
+        }
     }
 # endif /* FIONREAD */
 %}.
@@ -10918,8 +10924,8 @@
 %{
 #ifdef __SCHTEAM__
     {
-	int avail = fd.streamAvailable();
-	return __c__._RETURN (avail > 0 ? STObject.True : STObject.False);
+        int avail = fd.streamAvailable();
+        return __c__._RETURN (avail > 0 ? STObject.True : STObject.False);
     }
     /* NOTREACHED */
 #else
@@ -10928,11 +10934,11 @@
      */
 # if 0 && defined(FIONREAD)
     if (__isSmallInteger(fd)) {
-	int result = 0;
-
-	if (ioctl(__smallIntegerVal(fd), FIONREAD, &result) >= 0) {
-	    RETURN(result > 0 ? true : false);
-	}
+        int result = 0;
+
+        if (ioctl(__smallIntegerVal(fd), FIONREAD, &result) >= 0) {
+            RETURN(result > 0 ? true : false);
+        }
     }
 # endif /* FIONREAD */
 #endif
@@ -10942,9 +10948,9 @@
 !
 
 selectOnAnyReadable:readFdArray writable:writeFdArray exception:exceptFdArray
-	readableInto:readableResultFdArray writableInto:writableResultFdArray
-	exceptionInto:exceptionResultFdArray
-	withTimeOut:millis
+        readableInto:readableResultFdArray writableInto:writableResultFdArray
+        exceptionInto:exceptionResultFdArray
+        withTimeOut:millis
 
     "wait for any fd in readFdArray (an Array of integers) to become ready for reading,
      writeFdArray to become ready for writing,
@@ -10974,32 +10980,32 @@
     int numFds = 0;
 
     if (readableResultFdArray != nil) {
-	if (! __isArrayLike(readableResultFdArray)) {
-	    goto fail;
-	}
-	resultSizeReadable = __arraySize(readableResultFdArray);
+        if (! __isArrayLike(readableResultFdArray)) {
+            goto fail;
+        }
+        resultSizeReadable = __arraySize(readableResultFdArray);
     }
     if (writableResultFdArray != nil) {
-	if (! __isArrayLike(writableResultFdArray)) {
-	    goto fail;
-	}
-	resultSizeWritable = __arraySize(writableResultFdArray);
-	if (readableResultFdArray == writableResultFdArray) {
-	    // allow common result set for read/write/except
-	    pcntW = &cntR;
-	}
+        if (! __isArrayLike(writableResultFdArray)) {
+            goto fail;
+        }
+        resultSizeWritable = __arraySize(writableResultFdArray);
+        if (readableResultFdArray == writableResultFdArray) {
+            // allow common result set for read/write/except
+            pcntW = &cntR;
+        }
     }
     if (exceptionResultFdArray != nil) {
-	if (! __isArrayLike(exceptionResultFdArray)) {
-	    goto fail;
-	}
-	resultSizeException = __arraySize(exceptionResultFdArray);
-	if (exceptionResultFdArray == readableResultFdArray) {
-	    // allow common result set for read/write/except
-	    pcntE = &cntR;
-	} else if (exceptionResultFdArray == writableResultFdArray) {
-	    pcntE = &cntW;
-	}
+        if (! __isArrayLike(exceptionResultFdArray)) {
+            goto fail;
+        }
+        resultSizeException = __arraySize(exceptionResultFdArray);
+        if (exceptionResultFdArray == readableResultFdArray) {
+            // allow common result set for read/write/except
+            pcntE = &cntR;
+        } else if (exceptionResultFdArray == writableResultFdArray) {
+            pcntE = &cntW;
+        }
     }
 
     FD_ZERO(&rset);
@@ -11008,121 +11014,121 @@
 
     maxF = -1;
     if (readFdArray != nil) {
-	int i, count;
-
-	if (! __isArrayLike(readFdArray)) {
-	    goto fail;
-	}
-	count = __arraySize(readFdArray);
-
-	for (i=0; i<count;i++) {
-	    OBJ fd;
-
-	    fd = __arrayVal(readFdArray)[i];
-	    if (fd != nil) {
-		if (! __isSmallInteger(fd)) {
-		    if (@global(InfoPrinting) == true) {
-			fprintf(stderr, "OS [warning]: funny read-fd (0x%lx) given to select\n", (unsigned long)fd);
-		    }
-		} else {
-		    int f;
-
-		    f = __intVal(fd);
-		    if ((unsigned)f < FD_SETSIZE) {
-			FD_SET(f, &rset);
-			if (f > maxF) maxF = f;
-			numFds++;
-		    } else {
-			if (@global(InfoPrinting) == true) {
-			    fprintf(stderr, "OS [warning]: huge read-fd (0x%lx) given to select\n", (unsigned long)fd);
-			}
-		    }
-		}
-	    }
-	}
+        int i, count;
+
+        if (! __isArrayLike(readFdArray)) {
+            goto fail;
+        }
+        count = __arraySize(readFdArray);
+
+        for (i=0; i<count;i++) {
+            OBJ fd;
+
+            fd = __arrayVal(readFdArray)[i];
+            if (fd != nil) {
+                if (! __isSmallInteger(fd)) {
+                    if (@global(InfoPrinting) == true) {
+                        fprintf(stderr, "OS [warning]: funny read-fd (0x%lx) given to select\n", (unsigned long)fd);
+                    }
+                } else {
+                    int f;
+
+                    f = __intVal(fd);
+                    if ((unsigned)f < FD_SETSIZE) {
+                        FD_SET(f, &rset);
+                        if (f > maxF) maxF = f;
+                        numFds++;
+                    } else {
+                        if (@global(InfoPrinting) == true) {
+                            fprintf(stderr, "OS [warning]: huge read-fd (0x%lx) given to select\n", (unsigned long)fd);
+                        }
+                    }
+                }
+            }
+        }
     }
 
     if (writeFdArray != nil) {
-	int i, count;
-
-	if (! __isArrayLike(writeFdArray)) {
-	    goto fail;
-	}
-	count = __arraySize(writeFdArray);
-	for (i=0; i<count;i++) {
-	    OBJ fd;
-
-	    fd = __arrayVal(writeFdArray)[i];
-	    if (fd != nil) {
-		if (! __isSmallInteger(fd)) {
-		    if (@global(InfoPrinting) == true) {
-			fprintf(stderr, "OS [warning]: funny write-fd (0x%lx) given to select\n", (unsigned long)fd);
-		    }
-		} else {
-		    int f;
-
-		    f = __intVal(fd);
-		    if ((unsigned)f < FD_SETSIZE) {
-			FD_SET(f, &wset);
-			if (f > maxF) maxF = f;
-			numFds++;
-		    } else {
-			if (@global(InfoPrinting) == true) {
-			    fprintf(stderr, "OS [warning]: huge write-fd (0x%lx) given to select\n", (unsigned long)fd);
-			}
-		    }
-		}
-	    }
-	}
+        int i, count;
+
+        if (! __isArrayLike(writeFdArray)) {
+            goto fail;
+        }
+        count = __arraySize(writeFdArray);
+        for (i=0; i<count;i++) {
+            OBJ fd;
+
+            fd = __arrayVal(writeFdArray)[i];
+            if (fd != nil) {
+                if (! __isSmallInteger(fd)) {
+                    if (@global(InfoPrinting) == true) {
+                        fprintf(stderr, "OS [warning]: funny write-fd (0x%lx) given to select\n", (unsigned long)fd);
+                    }
+                } else {
+                    int f;
+
+                    f = __intVal(fd);
+                    if ((unsigned)f < FD_SETSIZE) {
+                        FD_SET(f, &wset);
+                        if (f > maxF) maxF = f;
+                        numFds++;
+                    } else {
+                        if (@global(InfoPrinting) == true) {
+                            fprintf(stderr, "OS [warning]: huge write-fd (0x%lx) given to select\n", (unsigned long)fd);
+                        }
+                    }
+                }
+            }
+        }
     }
 
     if (exceptFdArray != nil) {
-	int i, count;
-
-	if (! __isArrayLike(exceptFdArray)) {
-	    goto fail;
-	}
-	count = __arraySize(exceptFdArray);
-	for (i=0; i<count;i++) {
-	    OBJ fd;
-
-	    fd = __arrayVal(exceptFdArray)[i];
-	    if (fd != nil) {
-		if (! __isSmallInteger(fd)) {
-		    if (@global(InfoPrinting) == true) {
-			fprintf(stderr, "OS [warning]: funny except-fd (0x%lx) given to select\n", (unsigned long)fd);
-		    }
-		} else {
-		    int f;
-
-		    f = __intVal(fd);
-		    if ((unsigned)f < FD_SETSIZE) {
-			FD_SET(f, &eset);
-			if (f > maxF) maxF = f;
-			numFds++;
-		    } else {
-			if (@global(InfoPrinting) == true) {
-			    fprintf(stderr, "OS [warning]: huge except-fd (0x%lx) given to select\n", (unsigned long)fd);
-			}
-		    }
-		}
-	    }
-	}
+        int i, count;
+
+        if (! __isArrayLike(exceptFdArray)) {
+            goto fail;
+        }
+        count = __arraySize(exceptFdArray);
+        for (i=0; i<count;i++) {
+            OBJ fd;
+
+            fd = __arrayVal(exceptFdArray)[i];
+            if (fd != nil) {
+                if (! __isSmallInteger(fd)) {
+                    if (@global(InfoPrinting) == true) {
+                        fprintf(stderr, "OS [warning]: funny except-fd (0x%lx) given to select\n", (unsigned long)fd);
+                    }
+                } else {
+                    int f;
+
+                    f = __intVal(fd);
+                    if ((unsigned)f < FD_SETSIZE) {
+                        FD_SET(f, &eset);
+                        if (f > maxF) maxF = f;
+                        numFds++;
+                    } else {
+                        if (@global(InfoPrinting) == true) {
+                            fprintf(stderr, "OS [warning]: huge except-fd (0x%lx) given to select\n", (unsigned long)fd);
+                        }
+                    }
+                }
+            }
+        }
     }
 
     if (millis == nil) {
-	wtp = NULL;         // wait forever
+        wtp = NULL;         // wait forever
     } else if (__isSmallInteger(millis)) {
-	__millis = __intVal(millis);
-	if (__millis > 0) {
-	    wt.tv_sec = __millis / 1000;
-	    wt.tv_usec = (__millis % 1000) * 1000;
-	} else {
-	    wt.tv_sec = wt.tv_usec = 0;
-	}
-	wtp = &wt;
+        __millis = __intVal(millis);
+        if (__millis > 0) {
+            wt.tv_sec = __millis / 1000;
+            wt.tv_usec = (__millis % 1000) * 1000;
+        } else {
+            wt.tv_sec = wt.tv_usec = 0;
+        }
+        wtp = &wt;
     } else {
-	goto fail;
+        goto fail;
     }
 
     /*
@@ -11132,74 +11138,74 @@
     __BEGIN_INTERRUPTABLE__
 
     if (__millis == 0) {
-	/*
-	 * if there is no timeout time, we can stay here interruptable.
-	 */
-	do {
-	    ret = select(maxF+1, &rset, &wset, &eset, wtp);
-	} while ((ret < 0) && (errno == EINTR));
+        /*
+         * if there is no timeout time, we can stay here interruptable.
+         */
+        do {
+            ret = select(maxF+1, &rset, &wset, &eset, wtp);
+        } while ((ret < 0) && (errno == EINTR));
     } else {
-	do {
-	    ret = select(maxF+1, &rset, &wset, &eset, wtp);
-	    /*
-	     * for now: don't loop; if we did, we had to adjust the vt-timeval;
-	     * could otherwise stay in this loop forever ...
-	     * Premature ret (before the time expired) must be handled by the caller.
-	     * A good solution is to update the wt-timeval and redo the select.
-	     */
-	} while (0 /* (ret < 0) && (errno == EINTR) */ );
+        do {
+            ret = select(maxF+1, &rset, &wset, &eset, wtp);
+            /*
+             * for now: don't loop; if we did, we had to adjust the vt-timeval;
+             * could otherwise stay in this loop forever ...
+             * Premature ret (before the time expired) must be handled by the caller.
+             * A good solution is to update the wt-timeval and redo the select.
+             */
+        } while (0 /* (ret < 0) && (errno == EINTR) */ );
     }
     __END_INTERRUPTABLE__
 
     if (ret > 0) {
-	OBJ *__resultR = __arrayVal(readableResultFdArray);
-	OBJ *__resultW = __arrayVal(writableResultFdArray);
-	OBJ *__resultE = __arrayVal(exceptionResultFdArray);
-	int i;
-
-	for (i=0; i <= maxF; i++) {
-	    if (FD_ISSET(i, &rset)) {
-		if (*pcntR < resultSizeReadable) {
-		    __resultR[*pcntR] = __mkSmallInteger(i);
-		}
-		(*pcntR)++; cntAll++;
-	    }
-
-	    if (FD_ISSET(i, &wset)) {
-		if (*pcntW < resultSizeWritable) {
-		    __resultW[*pcntW] = __mkSmallInteger(i);
-		}
-		(*pcntW)++; cntAll++;
-	    }
-
-	    if (FD_ISSET(i, &eset)) {
-		if (*pcntE < resultSizeException) {
-		    __resultE[*pcntE] = __mkSmallInteger(i);
-		}
-		(*pcntE)++;  cntAll++;
-	    }
-	}
-	/* add a delimiter */
-	if (*pcntR < resultSizeReadable) {
-	    __resultR[*pcntR] = nil;
-	}
-	if (*pcntW < resultSizeWritable) {
-	    __resultW[*pcntW] = nil;
-	}
-	if (*pcntE < resultSizeException) {
-	    __resultE[*pcntE] = nil;
-	}
-
-	RETURN (__mkSmallInteger(cntAll));
+        OBJ *__resultR = __arrayVal(readableResultFdArray);
+        OBJ *__resultW = __arrayVal(writableResultFdArray);
+        OBJ *__resultE = __arrayVal(exceptionResultFdArray);
+        int i;
+
+        for (i=0; i <= maxF; i++) {
+            if (FD_ISSET(i, &rset)) {
+                if (*pcntR < resultSizeReadable) {
+                    __resultR[*pcntR] = __mkSmallInteger(i);
+                }
+                (*pcntR)++; cntAll++;
+            }
+
+            if (FD_ISSET(i, &wset)) {
+                if (*pcntW < resultSizeWritable) {
+                    __resultW[*pcntW] = __mkSmallInteger(i);
+                }
+                (*pcntW)++; cntAll++;
+            }
+
+            if (FD_ISSET(i, &eset)) {
+                if (*pcntE < resultSizeException) {
+                    __resultE[*pcntE] = __mkSmallInteger(i);
+                }
+                (*pcntE)++;  cntAll++;
+            }
+        }
+        /* add a delimiter */
+        if (*pcntR < resultSizeReadable) {
+            __resultR[*pcntR] = nil;
+        }
+        if (*pcntW < resultSizeWritable) {
+            __resultW[*pcntW] = nil;
+        }
+        if (*pcntE < resultSizeException) {
+            __resultE[*pcntE] = nil;
+        }
+
+        RETURN (__mkSmallInteger(cntAll));
     } else if (ret < 0 && errno != EINTR) {
-	/*
-	 * Error: Return -1
-	 */
-	if (@global(InfoPrinting) == true) {
-	    fprintf(stderr, "OS [info]: select errno = %d\n", errno);
-	}
-	@global(LastErrorNumber) = __mkSmallInteger(errno);
-	RETURN (__mkSmallInteger(-1));
+        /*
+         * Error: Return -1
+         */
+        if (@global(InfoPrinting) == true) {
+            fprintf(stderr, "OS [info]: select errno = %d\n", errno);
+        }
+        @global(LastErrorNumber) = __mkSmallInteger(errno);
+        RETURN (__mkSmallInteger(-1));
     }
 
     /*
@@ -11246,17 +11252,17 @@
 #  endif
 #  if defined(DELAY_FLAG)
     if (__isSmallInteger(fd)) {
-	int f = __intVal(fd);
-
-	flags = fcntl(f, F_GETFL, 0);
-	if (aBoolean == true) {
-	    ret = fcntl(f, F_SETFL, flags & ~DELAY_FLAG);
-	} else if (aBoolean == false) {
-	    ret = fcntl(f, F_SETFL, flags | DELAY_FLAG);
-	}
-	if (ret >= 0) {
-	    RETURN ((flags & DELAY_FLAG) ? false : true );
-	}
+        int f = __intVal(fd);
+
+        flags = fcntl(f, F_GETFL, 0);
+        if (aBoolean == true) {
+            ret = fcntl(f, F_SETFL, flags & ~DELAY_FLAG);
+        } else if (aBoolean == false) {
+            ret = fcntl(f, F_SETFL, flags | DELAY_FLAG);
+        }
+        if (ret >= 0) {
+            RETURN ((flags & DELAY_FLAG) ? false : true );
+        }
     }
 #   undef DELAY_FLAG
 #  endif
@@ -11300,7 +11306,7 @@
     DEFCONST(ELFDATANUM)
 
     DEFCONST(EI_VERSION)        /* File version byte index */
-				/* Value must be EV_CURRENT */
+                                /* Value must be EV_CURRENT */
 
     DEFCONST(EI_OSABI)          /* OS ABI identification */
     DEFCONST(ELFOSABI_NONE)     /* UNIX System V ABI */
@@ -11482,29 +11488,29 @@
 initializeOnFile: aStringOrFilename
     file := aStringOrFilename asFilename.
     file exists ifFalse:[
-	self error:'Given file does not exist'.
-	^ nil
+        self error:'Given file does not exist'.
+        ^ nil
     ].
     file isRegularFile ifFalse:[
-	self error:'Given file is not a regular file'.
-	^ nil
+        self error:'Given file is not a regular file'.
+        ^ nil
     ].
     file readingFileDo:[ :s |
-	s binary.
-	data := s next: 16r18.
-	(data at: 1 + EI_MAG0) ~~ ELFMAG0 ifTrue:[
-	    self error:'Given file is not a valid ELF file (magic not found)'.
-	].
-	(data at: 1 + EI_MAG1) ~~ ELFMAG1 ifTrue:[
-	    self error:'Given file is not a valid ELF file (magic not found)'.
-	].
-	(data at: 1 + EI_MAG2) ~~ ELFMAG2 ifTrue:[
-	    self error:'Given file is not a valid ELF file (magic not found)'.
-	].
-	(data at: 1 + EI_MAG3) ~~ ELFMAG3 ifTrue:[
-	    self error:'Given file is not a valid ELF file (magic not found)'.
-	].
-	msb := (data at: 1 + EI_DATA) == ELFDATA2MSB
+        s binary.
+        data := s next: 16r18.
+        (data at: 1 + EI_MAG0) ~~ ELFMAG0 ifTrue:[
+            self error:'Given file is not a valid ELF file (magic not found)'.
+        ].
+        (data at: 1 + EI_MAG1) ~~ ELFMAG1 ifTrue:[
+            self error:'Given file is not a valid ELF file (magic not found)'.
+        ].
+        (data at: 1 + EI_MAG2) ~~ ELFMAG2 ifTrue:[
+            self error:'Given file is not a valid ELF file (magic not found)'.
+        ].
+        (data at: 1 + EI_MAG3) ~~ ELFMAG3 ifTrue:[
+            self error:'Given file is not a valid ELF file (magic not found)'.
+        ].
+        msb := (data at: 1 + EI_DATA) == ELFDATA2MSB
     ].
 
     "Created: / 16-03-2015 / 16:13:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -11530,14 +11536,14 @@
     "one of our registered handles has been collected"
 
     aspect == #ElementExpired ifTrue:[
-	OpenFiles keysAndValuesDo:[:fd :handle |
-	    handle == 0 ifTrue:[
-		"Have to close the file descriptor"
-
-		OperatingSystem closeFd:fd.
-		OpenFiles at:fd put:nil.
-	    ].
-	].
+        OpenFiles keysAndValuesDo:[:fd :handle |
+            handle class == SmallInteger ifTrue:[
+                "Have to close the file descriptor"
+
+                OperatingSystem closeFd:fd.
+                OpenFiles at:fd put:nil.
+            ].
+        ].
     ].
 
     "Created: 30.9.1997 / 12:57:35 / stefan"
@@ -11550,7 +11556,7 @@
     OpenFiles addDependent:self.
 
     "
-	self initialize
+        self initialize
     "
 
     "Created: 26.9.1997 / 17:15:50 / stefan"
@@ -11574,7 +11580,7 @@
      or the error number as returned by the OperatingSystem"
 
     anErrorSymbolOrErrno isInteger ifTrue:[
-	(UnixOperatingSystem errorHolderForNumber:anErrorSymbolOrErrno) reportError
+        (UnixOperatingSystem errorHolderForNumber:anErrorSymbolOrErrno) reportError
     ].
     self primitiveFailed:anErrorSymbolOrErrno.
 ! !
@@ -11608,8 +11614,8 @@
     oldHandle := OpenFiles at:aFileDescriptor ifAbsent: [nil].
     "/ the 0 is possible, if an fd was open when saving a snapshot image,
     "/ and we come up in the new image with no one referring to it.
-    (oldHandle notNil and:[oldHandle ~~ 0 and:[ oldHandle ~~ self]]) ifTrue:[
-	oldHandle invalidate.
+    (oldHandle notNil and:[oldHandle class ~~ SmallInteger and:[ oldHandle ~~ self]]) ifTrue:[
+        oldHandle invalidate.
     ].
     self register.
 
@@ -11638,110 +11644,110 @@
     int nInstBytes, objSize;
 
     if (! __isSmallInteger(__INST(fd))) {
-	error = @symbol(errorNotOpen);
-	goto bad;
+        error = @symbol(errorNotOpen);
+        goto bad;
     }
     if (! __bothSmallInteger(count, firstIndex)) {
-	error = @symbol(badArgument);
-	goto bad;
+        error = @symbol(badArgument);
+        goto bad;
     }
     fd = __smallIntegerVal(__INST(fd));
     cnt = __smallIntegerVal(count);
     offs = __smallIntegerVal(firstIndex) - 1;
 
     if (fd < 0) {
-	error = @symbol(internalError);
-	goto bad;
+        error = @symbol(internalError);
+        goto bad;
     }
     if (__isExternalBytesLike(aByteBuffer)) {
-	OBJ sz;
-
-	nInstBytes = 0;
-	extPtr = (char *)(__externalBytesAddress(aByteBuffer));
-	if (extPtr == NULL) goto bad;
-	sz = __externalBytesSize(aByteBuffer);
-	if (__isSmallInteger(sz)) {
-	    objSize = __smallIntegerVal(sz);
-	} else {
-	    objSize = -1; /* unknown */
-	}
+        OBJ sz;
+
+        nInstBytes = 0;
+        extPtr = (char *)(__externalBytesAddress(aByteBuffer));
+        if (extPtr == NULL) goto bad;
+        sz = __externalBytesSize(aByteBuffer);
+        if (__isSmallInteger(sz)) {
+            objSize = __smallIntegerVal(sz);
+        } else {
+            objSize = -1; /* unknown */
+        }
     } else {
-	OBJ oClass = __Class(aByteBuffer);
-	int nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
-
-	nInstBytes = OHDR_SIZE + __OBJS2BYTES__(nInstVars);
-	switch (__intVal(__ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
-	    case BYTEARRAY:
-	    case WORDARRAY:
-	    case LONGARRAY:
-	    case SWORDARRAY:
-	    case SLONGARRAY:
-	    case FLOATARRAY:
-		break;
-	    case DOUBLEARRAY:
+        OBJ oClass = __Class(aByteBuffer);
+        int nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
+
+        nInstBytes = OHDR_SIZE + __OBJS2BYTES__(nInstVars);
+        switch (__intVal(__ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
+            case BYTEARRAY:
+            case WORDARRAY:
+            case LONGARRAY:
+            case SWORDARRAY:
+            case SLONGARRAY:
+            case FLOATARRAY:
+                break;
+            case DOUBLEARRAY:
 #ifdef __NEED_DOUBLE_ALIGN
-		nInstBytes = (nInstBytes-1+__DOUBLE_ALIGN) &~ (__DOUBLE_ALIGN-1);
-#endif
-		break;
-	    case LONGLONGARRAY:
-	    case SLONGLONGARRAY:
+                nInstBytes = (nInstBytes-1+__DOUBLE_ALIGN) &~ (__DOUBLE_ALIGN-1);
+#endif
+                break;
+            case LONGLONGARRAY:
+            case SLONGLONGARRAY:
 #ifdef __NEED_LONGLONG_ALIGN
-		nInstBytes = (nInstBytes-1+__LONGLONG_ALIGN) &~ (__LONGLONG_ALIGN-1);
-#endif
-		break;
-	    default:
-		goto bad;
-	}
-	extPtr = (char *)0;
-	objSize = __Size(aByteBuffer) - nInstBytes;
+                nInstBytes = (nInstBytes-1+__LONGLONG_ALIGN) &~ (__LONGLONG_ALIGN-1);
+#endif
+                break;
+            default:
+                goto bad;
+        }
+        extPtr = (char *)0;
+        objSize = __Size(aByteBuffer) - nInstBytes;
     }
     if ((offs >= 0)
-	&& (cnt >= 0)
-	&& ((objSize == -1) || (objSize >= (cnt + offs)))) {
-	nRead = 0;
-
-	do {
-	    int n;
-
-	    if (extPtr) {
-		n = read(fd, extPtr+offs, cnt);
-	    } else {
-		char *bp;
-
-		/*
-		 * on interrupt, anObject may be moved to another location.
-		 * So we recompute the byte-address here.
-		 */
-		bp = __byteArrayVal(aByteBuffer) + nInstBytes;
-
-		n = read(fd, bp + offs, cnt);
-	    }
-	    if (n > 0) {
-		cnt -= n;
-		offs += n;
-		nRead += n;
-	    } else if (n == 0) {
-		break;
-	    } else if (n < 0) {
-		if (0
+        && (cnt >= 0)
+        && ((objSize == -1) || (objSize >= (cnt + offs)))) {
+        nRead = 0;
+
+        do {
+            int n;
+
+            if (extPtr) {
+                n = read(fd, extPtr+offs, cnt);
+            } else {
+                char *bp;
+
+                /*
+                 * on interrupt, anObject may be moved to another location.
+                 * So we recompute the byte-address here.
+                 */
+                bp = __byteArrayVal(aByteBuffer) + nInstBytes;
+
+                n = read(fd, bp + offs, cnt);
+            }
+            if (n > 0) {
+                cnt -= n;
+                offs += n;
+                nRead += n;
+            } else if (n == 0) {
+                break;
+            } else if (n < 0) {
+                if (0
 #ifdef EWOULDBLOCK
-		    || errno == EWOULDBLOCK
+                    || errno == EWOULDBLOCK
 #endif
 #ifdef EAGAIN
-		    || errno == EAGAIN
-#endif
-		) {
-		     RETURN(nil);
-		}
-		if (errno != EINTR) {
-		     error = __mkSmallInteger(errno);
-		     goto bad;
-		}
-		__HANDLE_INTERRUPTS__;
-	    }
-	} while (cnt > 0);
-
-	RETURN (__mkSmallInteger(nRead));
+                    || errno == EAGAIN
+#endif
+                ) {
+                     RETURN(nil);
+                }
+                if (errno != EINTR) {
+                     error = __mkSmallInteger(errno);
+                     goto bad;
+                }
+                __HANDLE_INTERRUPTS__;
+            }
+        } while (cnt > 0);
+
+        RETURN (__mkSmallInteger(nRead));
     }
 bad: ;
 %}.
@@ -11780,110 +11786,110 @@
     int nInstBytes, objSize;
 
     if (! __isSmallInteger(__INST(fd))) {
-	error = @symbol(errorNotOpen);
-	goto bad;
+        error = @symbol(errorNotOpen);
+        goto bad;
     }
     if (! __bothSmallInteger(count, firstIndex)) {
-	error = @symbol(badArgument);
-	goto bad;
+        error = @symbol(badArgument);
+        goto bad;
     }
     fd = __smallIntegerVal(__INST(fd));
     cnt = __smallIntegerVal(count);
     offs = __smallIntegerVal(firstIndex) - 1;
 
     if (fd < 0) {
-	error = @symbol(internalError);
-	goto bad;
+        error = @symbol(internalError);
+        goto bad;
     }
     if (__isExternalBytesLike(aByteBuffer)) {
-	OBJ sz;
-
-	nInstBytes = 0;
-	extPtr = (char *)(__externalBytesAddress(aByteBuffer));
-	if (extPtr == NULL) goto bad;
-	sz = __externalBytesSize(aByteBuffer);
-	if (__isSmallInteger(sz)) {
-	    objSize = __smallIntegerVal(sz);
-	} else {
-	    objSize = -1; /* unknown */
-	}
+        OBJ sz;
+
+        nInstBytes = 0;
+        extPtr = (char *)(__externalBytesAddress(aByteBuffer));
+        if (extPtr == NULL) goto bad;
+        sz = __externalBytesSize(aByteBuffer);
+        if (__isSmallInteger(sz)) {
+            objSize = __smallIntegerVal(sz);
+        } else {
+            objSize = -1; /* unknown */
+        }
     } else {
-	OBJ oClass = __Class(aByteBuffer);
-	int nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
-
-	nInstBytes = OHDR_SIZE + __OBJS2BYTES__(nInstVars);
-	switch (__intVal(__ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
-	    case BYTEARRAY:
-	    case WORDARRAY:
-	    case LONGARRAY:
-	    case SWORDARRAY:
-	    case SLONGARRAY:
-	    case FLOATARRAY:
-		break;
-	    case DOUBLEARRAY:
+        OBJ oClass = __Class(aByteBuffer);
+        int nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
+
+        nInstBytes = OHDR_SIZE + __OBJS2BYTES__(nInstVars);
+        switch (__intVal(__ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
+            case BYTEARRAY:
+            case WORDARRAY:
+            case LONGARRAY:
+            case SWORDARRAY:
+            case SLONGARRAY:
+            case FLOATARRAY:
+                break;
+            case DOUBLEARRAY:
 #ifdef __NEED_DOUBLE_ALIGN
-		nInstBytes = (nInstBytes-1+__DOUBLE_ALIGN) &~ (__DOUBLE_ALIGN-1);
-#endif
-		break;
-	    case LONGLONGARRAY:
-	    case SLONGLONGARRAY:
+                nInstBytes = (nInstBytes-1+__DOUBLE_ALIGN) &~ (__DOUBLE_ALIGN-1);
+#endif
+                break;
+            case LONGLONGARRAY:
+            case SLONGLONGARRAY:
 #ifdef __NEED_LONGLONG_ALIGN
-		nInstBytes = (nInstBytes-1+__LONGLONG_ALIGN) &~ (__LONGLONG_ALIGN-1);
-#endif
-		break;
-	    default:
-		goto bad;
-	}
-	extPtr = (char *)0;
-	objSize = __Size(aByteBuffer) - nInstBytes;
+                nInstBytes = (nInstBytes-1+__LONGLONG_ALIGN) &~ (__LONGLONG_ALIGN-1);
+#endif
+                break;
+            default:
+                goto bad;
+        }
+        extPtr = (char *)0;
+        objSize = __Size(aByteBuffer) - nInstBytes;
     }
     if ((offs >= 0)
-	&& (cnt >= 0)
-	&& ((objSize == -1) || (objSize >= (cnt + offs)))) {
-	nWritten = 0;
-
-	do {
-	    int n;
-
-	    if (extPtr) {
-		n = write(fd, extPtr+offs, cnt);
-	    } else {
-		char *bp;
-
-		/*
-		 * on interrupt, anObject may be moved to another location.
-		 * So we recompute the byte-address here.
-		 */
-		bp = __byteArrayVal(aByteBuffer) + nInstBytes;
-
-		n = write(fd, bp + offs, cnt);
-	    }
-	    if (n > 0) {
-		cnt -= n;
-		offs += n;
-		nWritten += n;
-	    } else if (n == 0) {
-		break;
-	    } else if (n < 0) {
-		if (0
+        && (cnt >= 0)
+        && ((objSize == -1) || (objSize >= (cnt + offs)))) {
+        nWritten = 0;
+
+        do {
+            int n;
+
+            if (extPtr) {
+                n = write(fd, extPtr+offs, cnt);
+            } else {
+                char *bp;
+
+                /*
+                 * on interrupt, anObject may be moved to another location.
+                 * So we recompute the byte-address here.
+                 */
+                bp = __byteArrayVal(aByteBuffer) + nInstBytes;
+
+                n = write(fd, bp + offs, cnt);
+            }
+            if (n > 0) {
+                cnt -= n;
+                offs += n;
+                nWritten += n;
+            } else if (n == 0) {
+                break;
+            } else if (n < 0) {
+                if (0
 #ifdef EWOULDBLOCK
-		    || errno == EWOULDBLOCK
+                    || errno == EWOULDBLOCK
 #endif
 #ifdef EAGAIN
-		    || errno == EAGAIN
-#endif
-		) {
-		     RETURN(nil);
-		}
-		if (errno != EINTR) {
-		     error = __mkSmallInteger(errno);
-		     goto bad;
-		}
-		__HANDLE_INTERRUPTS__;
-	    }
-	} while (cnt > 0);
-
-	RETURN (__mkSmallInteger(nWritten));
+                    || errno == EAGAIN
+#endif
+                ) {
+                     RETURN(nil);
+                }
+                if (errno != EINTR) {
+                     error = __mkSmallInteger(errno);
+                     goto bad;
+                }
+                __HANDLE_INTERRUPTS__;
+            }
+        } while (cnt > 0);
+
+        RETURN (__mkSmallInteger(nWritten));
     }
 bad: ;
 %}.
@@ -11934,50 +11940,50 @@
     OBJ rslt;
 
     if (! __isSmallInteger(__INST(fd))) {
-	error = @symbol(errorNotOpen);
-	goto bad;
+        error = @symbol(errorNotOpen);
+        goto bad;
     }
     if (__isSmallInteger(newPosition)) {
-	pos = __smallIntegerVal(newPosition);
+        pos = __smallIntegerVal(newPosition);
     } else {
-	pos = __signedLongIntVal(newPosition);
-	if (pos < 0 && (sizeof(pos) < 8 || __signedLong64IntVal(newPosition, &pos) == 0)) {
-	    error = @symbol(badArgument1);
-	    goto bad;
-	}
+        pos = __signedLongIntVal(newPosition);
+        if (pos < 0 && (sizeof(pos) < 8 || __signedLong64IntVal(newPosition, &pos) == 0)) {
+            error = @symbol(badArgument1);
+            goto bad;
+        }
     }
 
     fd = __smallIntegerVal(__INST(fd));
     if (fd < 0) {
-	error = @symbol(internalError);
-	goto bad;
+        error = @symbol(internalError);
+        goto bad;
     }
     if (whence == @symbol(begin)) {
-	__whence = SEEK_SET;
+        __whence = SEEK_SET;
     } else if (whence == @symbol(current)) {
-	__whence = SEEK_CUR;
+        __whence = SEEK_CUR;
     } else if (whence == @symbol(end)) {
-	__whence = SEEK_END;
+        __whence = SEEK_END;
     } else {
-	error = @symbol(badArgument2);
-	goto bad;
+        error = @symbol(badArgument2);
+        goto bad;
     }
 
 again:
     ret = lseek(fd, pos, __whence);
     if (ret < 0) {
-	if (errno == EINTR) {
-	    __HANDLE_INTERRUPTS__;
-	    goto again;
-	}
-	error = __mkSmallInteger(errno);
-	goto bad;
+        if (errno == EINTR) {
+            __HANDLE_INTERRUPTS__;
+            goto again;
+        }
+        error = __mkSmallInteger(errno);
+        goto bad;
     }
 
     if (sizeof(ret) == 8) {
-	rslt = __MKINT64 (&ret);
+        rslt = __MKINT64 (&ret);
     } else {
-	rslt = __MKINT(ret);
+        rslt = __MKINT(ret);
     }
     RETURN (rslt);
 
@@ -12004,9 +12010,9 @@
      Experimental."
 
     ^ OperatingSystem selectOnAnyReadable:(Array with:fd)
-		      writable:(Array with:fd)
-		     exception:nil
-		   withTimeOut:millis
+                      writable:(Array with:fd)
+                     exception:nil
+                   withTimeOut:millis
 
     "Created: 1.10.1997 / 08:51:11 / stefan"
 !
@@ -12037,19 +12043,19 @@
 #  endif
 #  if defined(DELAY_FLAG)
     if (__isSmallInteger(__INST(fd))) {
-	int f = __intVal(__INST(fd));
-
-	flags = fcntl(f, F_GETFL, 0);
-	if (aBoolean == true) {
-	    ret = fcntl(f, F_SETFL, flags & ~DELAY_FLAG);
-	} else {
-	    ret = fcntl(f, F_SETFL, flags | DELAY_FLAG);
-	}
-	if (ret >= 0) {
-	    RETURN(__mkSmallInteger(flags));
-	} else {
-	    err = __mkSmallInteger(errno);
-	}
+        int f = __intVal(__INST(fd));
+
+        flags = fcntl(f, F_GETFL, 0);
+        if (aBoolean == true) {
+            ret = fcntl(f, F_SETFL, flags & ~DELAY_FLAG);
+        } else {
+            ret = fcntl(f, F_SETFL, flags | DELAY_FLAG);
+        }
+        if (ret >= 0) {
+            RETURN(__mkSmallInteger(flags));
+        } else {
+            err = __mkSmallInteger(errno);
+        }
     }
 #  undef DELAY_FLAG
 #  endif /* DELAY_FLAG */
@@ -12057,7 +12063,7 @@
 #endif /* not SCHTEAM */
 %}.
     err notNil ifTrue:[
-	self error:err
+        self error:err
     ].
 
     "
@@ -12077,7 +12083,7 @@
     OBJ handle = __externalAddressVal(self);
 
     if (__isSmallInteger(handle)) {
-	RETURN (handle);
+        RETURN (handle);
     }
 %}.
     ^ nil
@@ -12087,7 +12093,7 @@
 
 %{
     if (__isSmallInteger(anInteger)) {
-	__externalAddressVal(self) = (OBJ)(__smallIntegerVal(anInteger));
+        __externalAddressVal(self) = (OBJ)(__smallIntegerVal(anInteger));
     }
 %}
 
@@ -12105,37 +12111,37 @@
     int fd;
 
     if (__isSmallInteger(__INST(fd))) {
-	fd = __smallIntegerVal(__INST(fd));
-
-	/*
-	 * if available, try FIONREAD first, which is usually done faster.
-	 */
+        fd = __smallIntegerVal(__INST(fd));
+
+        /*
+         * if available, try FIONREAD first, which is usually done faster.
+         */
 # ifdef FIONREAD
-	{
-	    int result = 0;
-
-	    if (ioctl(fd, FIONREAD, &result) >= 0) {
-		RETURN(result > 0 ? true : false);
-	    }
-	}
+        {
+            int result = 0;
+
+            if (ioctl(fd, FIONREAD, &result) >= 0) {
+                RETURN(result > 0 ? true : false);
+            }
+        }
 # endif /* FIONREAD */
     }
 %}.
 
     OperatingSystem supportsSelect ifFalse:[
-	"/ mhmh - what should we do then ?
-	"/ For now, return true as if data was present,
-	"/ and let the thread fall into the read.
-	"/ It will then (hopefully) be desceduled there and
-	"/ effectively polling for input.
-
-	^ true
+        "/ mhmh - what should we do then ?
+        "/ For now, return true as if data was present,
+        "/ and let the thread fall into the read.
+        "/ It will then (hopefully) be desceduled there and
+        "/ effectively polling for input.
+
+        ^ true
     ].
 
     ^ (OperatingSystem selectOnAnyReadable:(Array with:fd)
-		       writable:nil
-		       exception:nil
-		       withTimeOut:0) == fd
+                       writable:nil
+                       exception:nil
+                       withTimeOut:0) == fd
 
     "
      |h n|
@@ -12158,18 +12164,18 @@
     "return true, if filedescriptor can be written without blocking"
 
     OperatingSystem supportsSelect ifFalse:[
-	"/ mhmh - what should we do then ?
-	"/ For now, return true as if data was present,
-	"/ and let the thread fall into the write.
-	"/ It will then (hopefully) be desceduled there and
-	"/ effectively polling for output.
-	^ true
+        "/ mhmh - what should we do then ?
+        "/ For now, return true as if data was present,
+        "/ and let the thread fall into the write.
+        "/ It will then (hopefully) be desceduled there and
+        "/ effectively polling for output.
+        ^ true
     ].
 
     ^ (OperatingSystem selectOnAnyReadable:nil
-		       writable:(Array with:fd)
-		       exception:nil
-		       withTimeOut:0) == fd
+                       writable:(Array with:fd)
+                       exception:nil
+                       withTimeOut:0) == fd
 !
 
 isValid
@@ -12188,13 +12194,13 @@
      */
 # if defined(FIONREAD)
     {
-	int n = 0;
-
-	if (__isSmallInteger(__INST(fd))) {
-	    if (ioctl(__smallIntegerVal(__INST(fd)), FIONREAD, &n) >= 0) {
-		RETURN (__MKINT(n));
-	    }
-	}
+        int n = 0;
+
+        if (__isSmallInteger(__INST(fd))) {
+            if (ioctl(__smallIntegerVal(__INST(fd)), FIONREAD, &n) >= 0) {
+                RETURN (__MKINT(n));
+            }
+        }
     }
 # endif /* FIONREAD */
 %}.
@@ -12218,21 +12224,21 @@
 
     sz := OpenFiles size.
     fd > sz ifTrue:[
-	"grow for more descriptors"
-	old := OpenFiles.
-
-	"JV@2013-03-15: It may happen that OS returns a filedescriptor whose value
-	 is larger than twice the lenght of the weakarray. Care for this.
-	 Spotted by Martin Kobetic."
-	OpenFiles := WeakArray new:((sz * 2) max:fd).
-	old removeDependent:(self class).
-	OpenFiles addDependent:(self class).
-	old keysAndValuesDo:[:index :elem|
-	    "be careful to not overwrite new entries in OpenFiles"
-	    elem notNil ifTrue:[
-		OpenFiles at:index put:elem.
-	    ].
-	].
+        "grow for more descriptors"
+        old := OpenFiles.
+
+        "JV@2013-03-15: It may happen that OS returns a filedescriptor whose value
+         is larger than twice the lenght of the weakarray. Care for this.
+         Spotted by Martin Kobetic."
+        OpenFiles := WeakArray new:((sz * 2) max:fd).
+        old removeDependent:(self class).
+        OpenFiles addDependent:(self class).
+        old keysAndValuesDo:[:index :elem|
+            "be careful to not overwrite new entries in OpenFiles"
+            elem notNil ifTrue:[
+                OpenFiles at:index put:elem.
+            ].
+        ].
     ].
     OpenFiles at:fd put:self.
 
@@ -12266,25 +12272,25 @@
 
     fd isNil ifTrue:[^ self error:#errorNotOpen].
     self canReadWithoutBlocking ifTrue:[
-	^ false.
+        ^ false.
     ].
 
     wasBlocked := OperatingSystem blockInterrupts.
     inputSema := Semaphore new name:'readWait'.
     [
-	timeout notNil ifTrue:[
-	    Processor signal:inputSema afterMilliseconds:timeout
-	].
-	Processor signal:inputSema onInput:fd.
-	Processor activeProcess state:#ioWait.
-	inputSema wait.
-	hasData := self canReadWithoutBlocking.
+        timeout notNil ifTrue:[
+            Processor signal:inputSema afterMilliseconds:timeout
+        ].
+        Processor signal:inputSema onInput:fd.
+        Processor activeProcess state:#ioWait.
+        inputSema wait.
+        hasData := self canReadWithoutBlocking.
     ] ifCurtailed:[
-	Processor disableSemaphore:inputSema.
-	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+        Processor disableSemaphore:inputSema.
+        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ].
     timeout notNil ifTrue:[
-	Processor disableSemaphore:inputSema.
+        Processor disableSemaphore:inputSema.
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ^ hasData not
@@ -12301,25 +12307,25 @@
 
     fd isNil ifTrue:[^ self error:#errorNotOpen].
     self canWriteWithoutBlocking ifTrue:[
-	^ false.
+        ^ false.
     ].
 
     wasBlocked := OperatingSystem blockInterrupts.
     outputSema := Semaphore new name:'writeWait'.
     [
-	timeout notNil ifTrue:[
-	    Processor signal:outputSema afterMilliseconds:timeout
-	].
-	Processor signal:outputSema onOutput:fd.
-	Processor activeProcess state:#ioWait.
-	outputSema wait.
-	canWrite := self canWriteWithoutBlocking.
+        timeout notNil ifTrue:[
+            Processor signal:outputSema afterMilliseconds:timeout
+        ].
+        Processor signal:outputSema onOutput:fd.
+        Processor activeProcess state:#ioWait.
+        outputSema wait.
+        canWrite := self canWriteWithoutBlocking.
     ] ifCurtailed:[
-	Processor disableSemaphore:outputSema.
-	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+        Processor disableSemaphore:outputSema.
+        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ].
     timeout notNil ifTrue:[
-	Processor disableSemaphore:outputSema.
+        Processor disableSemaphore:outputSema.
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ^ canWrite not
@@ -12334,8 +12340,8 @@
     FILE *f = (FILE *)(__externalAddressVal(self));
 
     if (f) {
-	__externalAddressVal(self) = NULL;
-	fclose(f);
+        __externalAddressVal(self) = NULL;
+        fclose(f);
     }
 %}
 
@@ -12345,12 +12351,12 @@
 
 type:t mode:m uid:u gid:g size:s id:i accessed:aT modified:mT statusChanged:sT path:lP numLinks:nL
     ^ self basicNew
-	type:t mode:m uid:u gid:g size:s id:i accessed:aT modified:mT statusChanged:sT path:lP numLinks:nL
+        type:t mode:m uid:u gid:g size:s id:i accessed:aT modified:mT statusChanged:sT path:lP numLinks:nL
 !
 
 type:t mode:m uid:u gid:g size:s id:i accessed:aT modified:mT statusChanged:sT sourcePath:sP targetPath:tP numLinks:nL
     ^ self basicNew
-	type:t mode:m uid:u gid:g size:s id:i accessed:aT modified:mT statusChanged:sT sourcePath:sP targetPath:tP numLinks:nL
+        type:t mode:m uid:u gid:g size:s id:i accessed:aT modified:mT statusChanged:sT sourcePath:sP targetPath:tP numLinks:nL
 ! !
 
 !UnixOperatingSystem::FileStatusInfo methodsFor:'accessing'!
@@ -12359,8 +12365,8 @@
     "return accessed"
 
     accessed isInteger ifTrue:[
-	"/ lazy time conversion
-	accessed := Timestamp fromOSTime:(accessed * 1000).
+        "/ lazy time conversion
+        accessed := Timestamp fromOSTime:(accessed * 1000).
     ].
     ^ accessed
 !
@@ -12410,8 +12416,8 @@
     "return modified"
 
     modified isInteger ifTrue:[
-	"/ lazy time conversion
-	modified := Timestamp fromOSTime:(modified * 1000).
+        "/ lazy time conversion
+        modified := Timestamp fromOSTime:(modified * 1000).
     ].
     ^ modified
 !
@@ -12434,8 +12440,8 @@
 
 statusChangeTime
     statusChanged isInteger ifTrue:[
-	"/ lazy time conversion
-	statusChanged := Timestamp fromOSTime:(statusChanged * 1000).
+        "/ lazy time conversion
+        statusChanged := Timestamp fromOSTime:(statusChanged * 1000).
     ].
     ^ statusChanged
 !
@@ -12658,9 +12664,9 @@
 
 isSpecialFile
     ^ (type ~~ #directory
-	and:[type ~~ #remoteDirectory
-	and:[type ~~ #regular
-	and:[type ~~ #symbolicLink
+        and:[type ~~ #remoteDirectory
+        and:[type ~~ #regular
+        and:[type ~~ #symbolicLink
     ]]])
 !
 
@@ -12703,8 +12709,8 @@
 
 printOn:aStream
     aStream
-	nextPutAll:'MountInfo for ';
-	nextPutAll:mountPointPath.
+        nextPutAll:'MountInfo for ';
+        nextPutAll:mountPointPath.
 ! !
 
 !UnixOperatingSystem::MountInfo methodsFor:'queries'!
@@ -12722,20 +12728,20 @@
 
     [Instance variables:]
 
-	pid     <Integer>       OS-Process identifier
-
-	status  <Symbol>        either #exit #signal #stop #continue
-
-	code    <Integer>       either exitcode or signalnumber
-
-	core    <Boolean>       true if core has been dumped
+        pid     <Integer>       OS-Process identifier
+
+        status  <Symbol>        either #exit #signal #stop #continue
+
+        code    <Integer>       either exitcode or signalnumber
+
+        core    <Boolean>       true if core has been dumped
 
 
     [author:]
-	Stefan Vogel
+        Stefan Vogel
 
     [see also:]
-	OperatingSystem
+        OperatingSystem
 "
 ! !
 
@@ -12897,15 +12903,15 @@
 
 %{
     if (__isSmallInteger(aNameOrNumber) || aNameOrNumber == nil) {
-	RETURN(aNameOrNumber);
+        RETURN(aNameOrNumber);
     }
 %}.
 
     ProtocolCache notNil ifTrue:[
-	protocolCode := ProtocolCache at:(aNameOrNumber asSymbol) ifAbsent:[].
-	protocolCode notNil ifTrue:[
-	    ^ protocolCode.
-	].
+        protocolCode := ProtocolCache at:(aNameOrNumber asSymbol) ifAbsent:[].
+        protocolCode notNil ifTrue:[
+            ^ protocolCode.
+        ].
     ].
 
 %{
@@ -12913,21 +12919,21 @@
     struct protoent *protoent = 0;
 
     if (__isStringLike(aNameOrNumber)) {
-	protoent = getprotobyname((char *) __stringVal(aNameOrNumber));
-	if (protoent) {
-	    protocolCode = __mkSmallInteger(protoent->p_proto);
-	    protocolSymbol = __MKSYMBOL(protoent->p_name, 0);
-	}
+        protoent = getprotobyname((char *) __stringVal(aNameOrNumber));
+        if (protoent) {
+            protocolCode = __mkSmallInteger(protoent->p_proto);
+            protocolSymbol = __MKSYMBOL(protoent->p_name, 0);
+        }
     }
 #endif /*NO_SOCKET*/
 %}.
 
     protocolSymbol notNil ifTrue:[
-	ProtocolCache isNil ifTrue:[
-	    ProtocolCache := IdentityDictionary new.
-	].
-	"beware of polluting the protocol cache with aliases"
-	ProtocolCache at:protocolSymbol put:protocolCode.
+        ProtocolCache isNil ifTrue:[
+            ProtocolCache := IdentityDictionary new.
+        ].
+        "beware of polluting the protocol cache with aliases"
+        ProtocolCache at:protocolSymbol put:protocolCode.
     ].
     ^ protocolCode
 
@@ -12944,10 +12950,10 @@
     |protocolSymbol|
 
     ProtocolCache notNil ifTrue:[
-	protocolSymbol := ProtocolCache keyAtIdentityValue:anInteger ifAbsent:[].
-	protocolSymbol notNil ifTrue:[
-	    ^ protocolSymbol.
-	].
+        protocolSymbol := ProtocolCache keyAtIdentityValue:anInteger ifAbsent:[].
+        protocolSymbol notNil ifTrue:[
+            ^ protocolSymbol.
+        ].
     ].
 
 %{
@@ -12955,19 +12961,19 @@
     struct protoent *protoent = 0;
 
     if (__isSmallInteger(anInteger)) {
-	protoent = getprotobynumber(__intVal(anInteger));
-	if (protoent) {
-	    protocolSymbol = __MKSYMBOL(protoent->p_name, 0);
-	}
+        protoent = getprotobynumber(__intVal(anInteger));
+        if (protoent) {
+            protocolSymbol = __MKSYMBOL(protoent->p_name, 0);
+        }
     }
 #endif /*NO_SOCKET*/
 %}.
 
     protocolSymbol notNil ifTrue:[
-	ProtocolCache isNil ifTrue:[
-	    ProtocolCache := IdentityDictionary new.
-	].
-	ProtocolCache at:protocolSymbol put:anInteger.
+        ProtocolCache isNil ifTrue:[
+            ProtocolCache := IdentityDictionary new.
+        ].
+        ProtocolCache at:protocolSymbol put:anInteger.
     ].
     ^ protocolSymbol
 
@@ -13000,88 +13006,88 @@
     type := OperatingSystem socketTypeCodeOf:typeArg.
     proto := self protocolCodeOf:protoArg.
     serviceNameArg notNil ifTrue:[
-	serviceName := serviceNameArg printString.      "convert integer port numbers"
+        serviceName := serviceNameArg printString.      "convert integer port numbers"
     ].
 
     hostName isNil ifTrue:[
-	encodedHostName := nil.
+        encodedHostName := nil.
     ] ifFalse:[
-	encodedHostName := hostName utf8Encoded.
+        encodedHostName := hostName utf8Encoded.
     ].
     (encodedHostName ~~ hostName and:[OperatingSystem getCodeset ~~ #utf8]) ifTrue:[
-	"hostName is not plain ASCII - so this is an IDN domain name. Have to ensure, that the locale is UTF-8.
-	 Block interrupt to not affect other ST/X processes while the locale is changed."
-	|interruptsBlocked oldLocale|
-
-	interruptsBlocked := OperatingSystem blockInterrupts.
-	oldLocale := OperatingSystem setLocale:#'LC_CTYPE' to:nil.
-	OperatingSystem setLocale:#'LC_CTYPE' to:'en_US.UTF-8'.
-	result := self primGetAddressInfo:encodedHostName serviceName:serviceName domainCode:domain socketTypeCode:type protocolCode:proto flags:flags.
-	OperatingSystem setLocale:#'LC_CTYPE' to:oldLocale.
-	interruptsBlocked ifFalse:[
-	    OperatingSystem unblockInterrupts.
-	].
+        "hostName is not plain ASCII - so this is an IDN domain name. Have to ensure, that the locale is UTF-8.
+         Block interrupt to not affect other ST/X processes while the locale is changed."
+        |interruptsBlocked oldLocale|
+
+        interruptsBlocked := OperatingSystem blockInterrupts.
+        oldLocale := OperatingSystem setLocale:#'LC_CTYPE' to:nil.
+        OperatingSystem setLocale:#'LC_CTYPE' to:'en_US.UTF-8'.
+        result := self primGetAddressInfo:encodedHostName serviceName:serviceName domainCode:domain socketTypeCode:type protocolCode:proto flags:flags.
+        OperatingSystem setLocale:#'LC_CTYPE' to:oldLocale.
+        interruptsBlocked ifFalse:[
+            OperatingSystem unblockInterrupts.
+        ].
     ] ifFalse:[
-	result := self primGetAddressInfo:encodedHostName serviceName:serviceName domainCode:domain socketTypeCode:type protocolCode:proto flags:flags.
+        result := self primGetAddressInfo:encodedHostName serviceName:serviceName domainCode:domain socketTypeCode:type protocolCode:proto flags:flags.
     ].
     result isArray ifFalse:[
-	|request|
-	request := SocketAddressInfo new
-	    domain:domainArg;
-	    type:typeArg;
-	    protocol:protoArg;
-	    canonicalName:hostName;
-	    serviceName:serviceName.
-	^ (HostNameLookupError new
-		parameter:result;
-		messageText:' - ', (result printString);
-		request:request) raiseRequest.
+        |request|
+        request := SocketAddressInfo new
+            domain:domainArg;
+            type:typeArg;
+            protocol:protoArg;
+            canonicalName:hostName;
+            serviceName:serviceName.
+        ^ (HostNameLookupError new
+                parameter:result;
+                messageText:' - ', (result printString);
+                request:request) raiseRequest.
     ].
     1 to:result size do:[:i |
-	|entry dom info|
-
-	entry := result at:i.
-
-	info := SocketAddressInfo new.
-	info
-	    flags:(entry at:1);
-	    domain:(dom := OperatingSystem domainSymbolOf:(entry at:2));
-	    type:(OperatingSystem socketTypeSymbolOf:(entry at:3));
-	    protocol:(self protocolSymbolOf:(entry at:4));
-	    socketAddress:((SocketAddress newDomain:dom) fromBytes:(entry at:5));
-	    canonicalName:(entry at:6).
-
-	result at:i put:info.
+        |entry dom info|
+
+        entry := result at:i.
+
+        info := SocketAddressInfo new.
+        info
+            flags:(entry at:1);
+            domain:(dom := OperatingSystem domainSymbolOf:(entry at:2));
+            type:(OperatingSystem socketTypeSymbolOf:(entry at:3));
+            protocol:(self protocolSymbolOf:(entry at:4));
+            socketAddress:((SocketAddress newDomain:dom) fromBytes:(entry at:5));
+            canonicalName:(entry at:6).
+
+        result at:i put:info.
     ].
     ^ result
 
     "
      self getAddressInfo:'localhost' serviceName:nil
-	    domain:nil type:nil protocol:nil flags:nil
+            domain:nil type:nil protocol:nil flags:nil
      self getAddressInfo:'localhost' serviceName:nil
-	    domain:#inet type:#stream protocol:nil flags:nil
+            domain:#inet type:#stream protocol:nil flags:nil
      self getAddressInfo:'localhost' serviceName:nil
-	    domain:#inet type:#stream protocol:#tcp flags:nil
+            domain:#inet type:#stream protocol:#tcp flags:nil
      self getAddressInfo:'blurb.exept.de' serviceName:nil
-	    domain:#inet type:nil protocol:nil flags:nil
+            domain:#inet type:nil protocol:nil flags:nil
      self getAddressInfo:'1.2.3.4' serviceName:'bla'
-	    domain:#inet type:nil protocol:nil flags:nil
+            domain:#inet type:nil protocol:nil flags:nil
      self getAddressInfo:'localhost' serviceName:'echo'
-	    domain:#inet type:nil protocol:nil flags:nil
+            domain:#inet type:nil protocol:nil flags:nil
      self getAddressInfo:nil serviceName:'echo'
-	    domain:#inet type:nil protocol:nil flags:nil
+            domain:#inet type:nil protocol:nil flags:nil
      self getAddressInfo:nil serviceName:nil
-	    domain:#inet type:nil protocol:nil flags:nil
+            domain:#inet type:nil protocol:nil flags:nil
      self getAddressInfo:'www.google.de' serviceName:nil
-	    domain:nil type:nil protocol:nil flags:nil
+            domain:nil type:nil protocol:nil flags:nil
      self getAddressInfo:'www.exept.de' serviceName:nil
-	    domain:nil type:nil protocol:nil flags:nil
+            domain:nil type:nil protocol:nil flags:nil
      self getAddressInfo:'www.exept.de' serviceName:nil
-	    domain:#'AF_INET' type:nil protocol:nil flags:nil
+            domain:#'AF_INET' type:nil protocol:nil flags:nil
      self getAddressInfo:'www.exept.de' serviceName:nil
-	    domain:#'AF_INET6' type:nil protocol:nil flags:nil
+            domain:#'AF_INET6' type:nil protocol:nil flags:nil
      self getAddressInfo:'www.baden-württemberg.de' serviceName:nil
-	    domain:#'AF_INET' type:#stream protocol:nil flags:nil
+            domain:#'AF_INET' type:#stream protocol:nil flags:nil
     "
 !
 
@@ -13113,20 +13119,20 @@
     int nInstBytes, sockAddrSize;
 
     if (wantHostName == true) {
-	hp = host;
-	hsz = sizeof(host);
+        hp = host;
+        hsz = sizeof(host);
     }
     if (wantServiceName == true) {
-	sp = service;
-	ssz = sizeof(service);
+        sp = service;
+        ssz = sizeof(service);
     }
     if (hp == 0 && sp == 0) {
-	error = @symbol(badArgument);
-	goto err;
+        error = @symbol(badArgument);
+        goto err;
     }
     if (!__isBytes(socketAddress)) {
-	error = @symbol(badArgument1);
-	goto err;
+        error = @symbol(badArgument1);
+        goto err;
     }
 
     nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(socketAddress))->c_ninstvars));
@@ -13134,187 +13140,187 @@
     sockAddrSize -= nInstBytes;
 
     if (!__isSmallInteger(flags)) {
-	error = @symbol(badArgument5);
-	goto err;
+        error = @symbol(badArgument5);
+        goto err;
     }
     __flags = __intVal(flags);
 
 #if defined(NI_NUMERICHOST)
     if (useDatagram == true) {
-	__flags |= NI_DGRAM;
+        __flags |= NI_DGRAM;
     }
 
     {
-	bp = (char *)(__byteArrayVal(socketAddress));
-	bp += nInstBytes;
-	__BEGIN_INTERRUPTABLE__
-	ret = getnameinfo((struct sockaddr *)bp, sockAddrSize,
-			  hp, hsz, sp, ssz, __flags);
-	__END_INTERRUPTABLE__
+        bp = (char *)(__byteArrayVal(socketAddress));
+        bp += nInstBytes;
+        __BEGIN_INTERRUPTABLE__
+        ret = getnameinfo((struct sockaddr *)bp, sockAddrSize,
+                          hp, hsz, sp, ssz, __flags);
+        __END_INTERRUPTABLE__
     } while (ret == EAI_SYSTEM && errno == EINTR);
     if (ret != 0) {
-	switch (ret) {
-	case EAI_FAMILY:
-	    error = @symbol(badProtocol);
-	    break;
-	case EAI_SOCKTYPE:
-	    error = @symbol(badSocketType);
-	    break;
-	case EAI_BADFLAGS:
-	    error = @symbol(badFlags);
-	    break;
-	case EAI_NONAME:
-	    error = @symbol(unknownHost);
-	    break;
-	case EAI_SERVICE:
-	    error = @symbol(unknownService);
-	    break;
+        switch (ret) {
+        case EAI_FAMILY:
+            error = @symbol(badProtocol);
+            break;
+        case EAI_SOCKTYPE:
+            error = @symbol(badSocketType);
+            break;
+        case EAI_BADFLAGS:
+            error = @symbol(badFlags);
+            break;
+        case EAI_NONAME:
+            error = @symbol(unknownHost);
+            break;
+        case EAI_SERVICE:
+            error = @symbol(unknownService);
+            break;
 #ifdef EAI_ADDRFAMILY
-	case EAI_ADDRFAMILY :
-	    error = @symbol(unknownHostForProtocol);
-	    break;
+        case EAI_ADDRFAMILY :
+            error = @symbol(unknownHostForProtocol);
+            break;
 #endif
 #ifdef EAI_NODATA
-	case EAI_NODATA:
-	    error = @symbol(noAddress);
-	    break;
-#endif
-	case EAI_MEMORY:
-	    error = @symbol(allocationFailure);
-	    break;
-	case EAI_FAIL:
-	    error = @symbol(permanentFailure);
-	    break;
-	case EAI_AGAIN:
-	    error = @symbol(tryAgain);
-	    break;
-	case EAI_SYSTEM:
-	    error = @symbol(systemError);
-	    break;
-	default:
-	    error = @symbol(unknownError);
-	}
-	errorString = __MKSTRING(gai_strerror(ret));
-	goto err;
+        case EAI_NODATA:
+            error = @symbol(noAddress);
+            break;
+#endif
+        case EAI_MEMORY:
+            error = @symbol(allocationFailure);
+            break;
+        case EAI_FAIL:
+            error = @symbol(permanentFailure);
+            break;
+        case EAI_AGAIN:
+            error = @symbol(tryAgain);
+            break;
+        case EAI_SYSTEM:
+            error = @symbol(systemError);
+            break;
+        default:
+            error = @symbol(unknownError);
+        }
+        errorString = __MKSTRING(gai_strerror(ret));
+        goto err;
     }
 # else /* ! NI_NUMERICHOST */
     {
-	/*
-	 * Do it using gethostbyaddr()
-	 */
-	struct sockaddr_in *sa;
-
-	if (sockAddrSize < sizeof(*sa)) {
-	    error = @symbol(badArgument1);
-	    goto err;
-	}
-	bp = (char *)(__byteArrayVal(socketAddress));
-	bp += nInstBytes;
-	sa = (struct sockaddr_in *)bp;
-
-	if (sp) {
-	    struct servent *servp;
-	    char *__proto = 0;
-
-	    __proto = (useDatagram == true ? "udp" : "tcp");
-
-	    servp = getservbyport(sa->sin_port, __proto);
-	    if (servp) {
-		sp = servp->s_name;
-	    }
-	}
-	if (hp) {
-	    struct hostent *hostp;
+        /*
+         * Do it using gethostbyaddr()
+         */
+        struct sockaddr_in *sa;
+
+        if (sockAddrSize < sizeof(*sa)) {
+            error = @symbol(badArgument1);
+            goto err;
+        }
+        bp = (char *)(__byteArrayVal(socketAddress));
+        bp += nInstBytes;
+        sa = (struct sockaddr_in *)bp;
+
+        if (sp) {
+            struct servent *servp;
+            char *__proto = 0;
+
+            __proto = (useDatagram == true ? "udp" : "tcp");
+
+            servp = getservbyport(sa->sin_port, __proto);
+            if (servp) {
+                sp = servp->s_name;
+            }
+        }
+        if (hp) {
+            struct hostent *hostp;
 #  ifdef USE_H_ERRNO
-	    do {
-		bp = (char *)(__byteArrayVal(socketAddress));
-		bp += nInstBytes;
-		sa = (struct sockaddr_in *)bp;
-
-		/* __BEGIN_INTERRUPTABLE__ is dangerous, because gethostbyname uses a static data area
-		 */
-		hostp = gethostbyaddr((char *)&sa->sin_addr, sockAddrSize, sa->sin_family);
-		/* __END_INTERRUPTABLE__ */
-	    } while ((hostp == NULL)
-		      && ((h_errno == TRY_AGAIN)
-			  || errno == EINTR
+            do {
+                bp = (char *)(__byteArrayVal(socketAddress));
+                bp += nInstBytes;
+                sa = (struct sockaddr_in *)bp;
+
+                /* __BEGIN_INTERRUPTABLE__ is dangerous, because gethostbyname uses a static data area
+                 */
+                hostp = gethostbyaddr((char *)&sa->sin_addr, sockAddrSize, sa->sin_family);
+                /* __END_INTERRUPTABLE__ */
+            } while ((hostp == NULL)
+                      && ((h_errno == TRY_AGAIN)
+                          || errno == EINTR
 #   ifdef IRIX5_3
-			  || (errno == ECONNREFUSED)
+                          || (errno == ECONNREFUSED)
 #   endif
-			 )
-	    );
-	    if (hostp == 0) {
-		switch (h_errno) {
-		case HOST_NOT_FOUND:
-		    errorString = @symbol(unknownHost);
-		    break;
-		case NO_ADDRESS:
-		    errorString = @symbol(noAddress);
-		    break;
-		case NO_RECOVERY:
-		    errorString = @symbol(permanentFailure);
-		    break;
-		case TRY_AGAIN:
-		    errorString = @symbol(tryAgain);
-		    break;
-		default:
-		    errorString = @symbol(unknownError);
-		    break;
-		}
-		error = __mkSmallInteger(h_errno);
-		goto err;
-	    }
+                         )
+            );
+            if (hostp == 0) {
+                switch (h_errno) {
+                case HOST_NOT_FOUND:
+                    errorString = @symbol(unknownHost);
+                    break;
+                case NO_ADDRESS:
+                    errorString = @symbol(noAddress);
+                    break;
+                case NO_RECOVERY:
+                    errorString = @symbol(permanentFailure);
+                    break;
+                case TRY_AGAIN:
+                    errorString = @symbol(tryAgain);
+                    break;
+                default:
+                    errorString = @symbol(unknownError);
+                    break;
+                }
+                error = __mkSmallInteger(h_errno);
+                goto err;
+            }
 #  else /* !USE_H_ERRNO */
-	    hostp = gethostbyaddr(sa->sin_addr, sockAddrSize, sa->sin_family);
-	    if (hostp == 0) {
-		errorString = @symbol(unknownHost);
-		error = __mkSmallInteger(-1);
-		goto err;
-	    }
+            hostp = gethostbyaddr(sa->sin_addr, sockAddrSize, sa->sin_family);
+            if (hostp == 0) {
+                errorString = @symbol(unknownHost);
+                error = __mkSmallInteger(-1);
+                goto err;
+            }
 #  endif /* !USE_H_ERRNO*/
-	    hp = hostp->h_name;
-	}
+            hp = hostp->h_name;
+        }
     }
 # endif /* ! NI_NUMERICHOST */
 
     if (hp)
-	hostName = __MKSTRING(hp);
+        hostName = __MKSTRING(hp);
     if (sp)
-	serviceName = __MKSTRING(sp);
+        serviceName = __MKSTRING(sp);
 err:;
 #else
     error = @symbol(notImplemented);
 #endif
 %}.
     error notNil ifTrue:[
-	^ (HostAddressLookupError new
-		parameter:error;
-		messageText:' - ', errorString;
-		request:thisContext message) raiseRequest.
+        ^ (HostAddressLookupError new
+                parameter:error;
+                messageText:' - ', errorString;
+                request:thisContext message) raiseRequest.
     ].
 
     ^ Array with:hostName with:serviceName
 
     "
      self getNameInfo:
-	(self getAddressInfo:'localhost' serviceName:'echo'
-		domain:#inet type:#stream protocol:nil flags:nil) first socketAddress
-	 wantHostName:true wantServiceName:true datagram:false flags:0
+        (self getAddressInfo:'localhost' serviceName:'echo'
+                domain:#inet type:#stream protocol:nil flags:nil) first socketAddress
+         wantHostName:true wantServiceName:true datagram:false flags:0
 
      self getNameInfo:
-	(self getAddressInfo:'exept.de' serviceName:'echo'
-		domain:#inet type:#stream protocol:nil flags:nil) first socketAddress
-	 wantHostName:true wantServiceName:true datagram:false flags:0
+        (self getAddressInfo:'exept.de' serviceName:'echo'
+                domain:#inet type:#stream protocol:nil flags:nil) first socketAddress
+         wantHostName:true wantServiceName:true datagram:false flags:0
 
      self getNameInfo:
-	(self getAddressInfo:'217.172.183.25' serviceName:'22'
-		domain:#inet type:#stream protocol:nil flags:nil) first socketAddress
-	 wantHostName:true wantServiceName:true datagram:false flags:0
+        (self getAddressInfo:'217.172.183.25' serviceName:'22'
+                domain:#inet type:#stream protocol:nil flags:nil) first socketAddress
+         wantHostName:true wantServiceName:true datagram:false flags:0
 
      self getNameInfo:
-	(self getAddressInfo:'1.2.3.4' serviceName:'22'
-		domain:#inet type:#stream protocol:nil flags:nil) first socketAddress
-	 wantHostName:true wantServiceName:true datagram:false flags:0
+        (self getAddressInfo:'1.2.3.4' serviceName:'22'
+                domain:#inet type:#stream protocol:nil flags:nil) first socketAddress
+         wantHostName:true wantServiceName:true datagram:false flags:0
     "
 !
 
@@ -13333,24 +13339,24 @@
     int ret, cnt = 0;
 
     if (hostName == nil) {
-	__hostName = 0;
+        __hostName = 0;
     } else if (__isStringLike(hostName)) {
-	__hostName = __stringVal(hostName);
+        __hostName = __stringVal(hostName);
     } else {
-	error = @symbol(badArgument1);
-	goto out;
+        error = @symbol(badArgument1);
+        goto out;
     }
     if (serviceName == nil) {
-	__serviceName = 0;
+        __serviceName = 0;
     } else if (__isStringLike(serviceName)) {
-	__serviceName = __stringVal(serviceName);
+        __serviceName = __stringVal(serviceName);
     } else {
-	error = @symbol(badArgument2);
-	goto out;
+        error = @symbol(badArgument2);
+        goto out;
     }
     if (__hostName == 0 && __serviceName == 0) {
-	error = @symbol(badArgument);
-	goto out;
+        error = @symbol(badArgument);
+        goto out;
     }
 
 {
@@ -13365,116 +13371,116 @@
     hints.ai_flags = AI_IDN | AI_CANONIDN;      // map non-ascii domain names to IDN format
 #endif
     if (__isSmallInteger(domain))
-	hints.ai_family = __intVal(domain);
+        hints.ai_family = __intVal(domain);
     if (__isSmallInteger(type))
-	hints.ai_socktype = __intVal(type);
+        hints.ai_socktype = __intVal(type);
     if (__isSmallInteger(proto))
-	hints.ai_protocol = __intVal(proto);
+        hints.ai_protocol = __intVal(proto);
     if (__isSmallInteger(flags))
-	hints.ai_flags |= __intVal(flags);
+        hints.ai_flags |= __intVal(flags);
 
     do {
-	/* reload */
-	if (__hostName) {
-	    __hostName = __stringVal(hostName);
-	}
-	if (__serviceName) {
-	    __serviceName = __stringVal(serviceName);
-	}
+        /* reload */
+        if (__hostName) {
+            __hostName = __stringVal(hostName);
+        }
+        if (__serviceName) {
+            __serviceName = __stringVal(serviceName);
+        }
 
 //        __BEGIN_INTERRUPTABLE__
-	ret = getaddrinfo(__hostName, __serviceName, &hints, &info);
+        ret = getaddrinfo(__hostName, __serviceName, &hints, &info);
 //        __END_INTERRUPTABLE__
     } while (ret == EAI_SYSTEM && errno == EINTR);
     if (ret != 0) {
-	switch (ret) {
-	case EAI_FAMILY:
-	    error = @symbol(badProtocol);
-	    break;
-	case EAI_SOCKTYPE:
-	    error = @symbol(badSocketType);
-	    break;
-	case EAI_BADFLAGS:
-	    error = @symbol(badFlags);
-	    break;
-	case EAI_NONAME:
-	    error = @symbol(unknownHost);
-	    break;
-	case EAI_SERVICE:
-	    error = @symbol(unknownService);
-	    break;
+        switch (ret) {
+        case EAI_FAMILY:
+            error = @symbol(badProtocol);
+            break;
+        case EAI_SOCKTYPE:
+            error = @symbol(badSocketType);
+            break;
+        case EAI_BADFLAGS:
+            error = @symbol(badFlags);
+            break;
+        case EAI_NONAME:
+            error = @symbol(unknownHost);
+            break;
+        case EAI_SERVICE:
+            error = @symbol(unknownService);
+            break;
 #ifdef EAI_ADDRFAMILY
-	case EAI_ADDRFAMILY :
-	    error = @symbol(unknownHostForProtocol);
-	    break;
+        case EAI_ADDRFAMILY :
+            error = @symbol(unknownHostForProtocol);
+            break;
 #endif
 #ifdef EAI_NODATA
-	case EAI_NODATA:
-	    error = @symbol(noAddress);
-	    break;
-#endif
-	case EAI_MEMORY:
-	    error = @symbol(allocationFailure);
-	    break;
-	case EAI_FAIL:
-	    error = @symbol(permanentFailure);
-	    break;
-	case EAI_AGAIN:
-	    error = @symbol(tryAgain);
-	    break;
-	case EAI_SYSTEM:
-	    error = @symbol(systemError);
-	    break;
-	default:
-	    error = @symbol(unknownError);
-	}
-	errorString = __MKSTRING(gai_strerror(ret));
-	goto err;
+        case EAI_NODATA:
+            error = @symbol(noAddress);
+            break;
+#endif
+        case EAI_MEMORY:
+            error = @symbol(allocationFailure);
+            break;
+        case EAI_FAIL:
+            error = @symbol(permanentFailure);
+            break;
+        case EAI_AGAIN:
+            error = @symbol(tryAgain);
+            break;
+        case EAI_SYSTEM:
+            error = @symbol(systemError);
+            break;
+        default:
+            error = @symbol(unknownError);
+        }
+        errorString = __MKSTRING(gai_strerror(ret));
+        goto err;
     }
     for (cnt=0, infop=info; infop; infop=infop->ai_next)
-	cnt++;
+        cnt++;
 
     result = __ARRAY_NEW_INT(cnt);
     if (result == nil) {
-	error = @symbol(allocationFailure);
-	goto err;
+        error = @symbol(allocationFailure);
+        goto err;
     }
     for (infop=info, cnt=0; infop; infop=infop->ai_next, cnt++) {
-	OBJ o, resp;
-
-	resp = __ARRAY_NEW_INT(6);
-	if (resp == nil) {
-	    error = @symbol(allocationFailure);
-	    goto err;
-	}
-
-	__ArrayInstPtr(result)->a_element[cnt] = resp; __STORE(result, resp);
-
-	__ArrayInstPtr(resp)->a_element[0] = __mkSmallInteger(infop->ai_flags);
-	__ArrayInstPtr(resp)->a_element[1] = __mkSmallInteger(infop->ai_family);
-	__ArrayInstPtr(resp)->a_element[2] = __mkSmallInteger(infop->ai_socktype);
-	__ArrayInstPtr(resp)->a_element[3] = __mkSmallInteger(infop->ai_protocol);
-
-	__PROTECT__(resp);
-	o = __BYTEARRAY_NEW_INT(infop->ai_addrlen);
-	__UNPROTECT__(resp);
-	if (o == nil) {
-	    error = @symbol(allocationFailure);
-	    goto err;
-	}
-	memcpy(__byteArrayVal(o), infop->ai_addr, infop->ai_addrlen);
+        OBJ o, resp;
+
+        resp = __ARRAY_NEW_INT(6);
+        if (resp == nil) {
+            error = @symbol(allocationFailure);
+            goto err;
+        }
+
+        __ArrayInstPtr(result)->a_element[cnt] = resp; __STORE(result, resp);
+
+        __ArrayInstPtr(resp)->a_element[0] = __mkSmallInteger(infop->ai_flags);
+        __ArrayInstPtr(resp)->a_element[1] = __mkSmallInteger(infop->ai_family);
+        __ArrayInstPtr(resp)->a_element[2] = __mkSmallInteger(infop->ai_socktype);
+        __ArrayInstPtr(resp)->a_element[3] = __mkSmallInteger(infop->ai_protocol);
+
+        __PROTECT__(resp);
+        o = __BYTEARRAY_NEW_INT(infop->ai_addrlen);
+        __UNPROTECT__(resp);
+        if (o == nil) {
+            error = @symbol(allocationFailure);
+            goto err;
+        }
+        memcpy(__byteArrayVal(o), infop->ai_addr, infop->ai_addrlen);
        __ArrayInstPtr(resp)->a_element[4] = o; __STORE(resp, o);
 
-	if (infop->ai_canonname) {
-	    __PROTECT__(resp);
-	    o = __MKSTRING(infop->ai_canonname);
-	    __UNPROTECT__(resp);
-	    if (o == nil) {
-		error = @symbol(allocationFailure);
-		goto err;
-	    }
-	    __ArrayInstPtr(resp)->a_element[5] = o; __STORE(resp, o);
-	}
+        if (infop->ai_canonname) {
+            __PROTECT__(resp);
+            o = __MKSTRING(infop->ai_canonname);
+            __UNPROTECT__(resp);
+            if (o == nil) {
+                error = @symbol(allocationFailure);
+                goto err;
+            }
+            __ArrayInstPtr(resp)->a_element[5] = o; __STORE(resp, o);
+        }
     }
 
 err:
@@ -13491,136 +13497,136 @@
     int i;
 
     if (__serviceName) {
-	struct servent *sp;
-	char *__proto = 0;
-
-	if (__isStringLike(protoArg))
-	    __proto = __stringVal(protoArg);
-
-	sp = getservbyname(__serviceName, __proto);
-	if (sp == NULL) {
-	    errorString = @symbol(unknownService);
-	    error = __mkSmallInteger(-3);
-	    goto err;
-	}
-	port = sp->s_port;
+        struct servent *sp;
+        char *__proto = 0;
+
+        if (__isStringLike(protoArg))
+            __proto = __stringVal(protoArg);
+
+        sp = getservbyname(__serviceName, __proto);
+        if (sp == NULL) {
+            errorString = @symbol(unknownService);
+            error = __mkSmallInteger(-3);
+            goto err;
+        }
+        port = sp->s_port;
     }
 
     if (__hostName) {
 #  ifdef USE_H_ERRNO
-	do {
-	    if (hostName == nil) {
-		__hostName = 0;
-	    } else if (__isStringLike(hostName)) {
-		__hostName = __stringVal(hostName);
-	    }
-	    /* __BEGIN_INTERRUPTABLE__ is dangerous, because gethostbyname
-	     * uses a static data area
-	     */
-	    __BEGIN_INTERRUPTABLE__
-	    hp = gethostbyname(__hostName);
-	    __END_INTERRUPTABLE__
-	} while ((hp == NULL)
-		  && (
-			(h_errno == TRY_AGAIN)
-		      || errno == EINTR
+        do {
+            if (hostName == nil) {
+                __hostName = 0;
+            } else if (__isStringLike(hostName)) {
+                __hostName = __stringVal(hostName);
+            }
+            /* __BEGIN_INTERRUPTABLE__ is dangerous, because gethostbyname
+             * uses a static data area
+             */
+            __BEGIN_INTERRUPTABLE__
+            hp = gethostbyname(__hostName);
+            __END_INTERRUPTABLE__
+        } while ((hp == NULL)
+                  && (
+                        (h_errno == TRY_AGAIN)
+                      || errno == EINTR
 #   ifdef IRIX5_3
-		      || (errno == ECONNREFUSED)
+                      || (errno == ECONNREFUSED)
 #   endif
-		     )
-	);
-	if (hp == 0) {
-	    switch (h_errno) {
-	    case HOST_NOT_FOUND:
-		errorString = @symbol(unknownHost);
-		break;
-	    case NO_ADDRESS:
-		errorString = @symbol(noAddress);
-		break;
-	    case NO_RECOVERY:
-		errorString = @symbol(permanentFailure);
-		break;
-	    case TRY_AGAIN:
-		errorString = @symbol(tryAgain);
-		break;
-	    default:
-		errorString = @symbol(unknownError);
-		break;
-	    }
-	    error = __mkSmallInteger(h_errno);
-	    goto err;
-	}
+                     )
+        );
+        if (hp == 0) {
+            switch (h_errno) {
+            case HOST_NOT_FOUND:
+                errorString = @symbol(unknownHost);
+                break;
+            case NO_ADDRESS:
+                errorString = @symbol(noAddress);
+                break;
+            case NO_RECOVERY:
+                errorString = @symbol(permanentFailure);
+                break;
+            case TRY_AGAIN:
+                errorString = @symbol(tryAgain);
+                break;
+            default:
+                errorString = @symbol(unknownError);
+                break;
+            }
+            error = __mkSmallInteger(h_errno);
+            goto err;
+        }
 #  else /* !USE_H_ERRNO */
-	hp = gethostbyname(__hostName);
-	if (hp == 0) {
-	    errorString = @symbol(unknownHost);
-	    error = __mkSmallInteger(-1);
-	    goto err;
-	}
+        hp = gethostbyname(__hostName);
+        if (hp == 0) {
+            errorString = @symbol(unknownHost);
+            error = __mkSmallInteger(-1);
+            goto err;
+        }
 #  endif /* !USE_H_ERRNO*/
 
-	if (__isSmallInteger(domain) && hp->h_addrtype != __smallIntegerVal(domain)) {
-	    errorString = @symbol(unknownHost);
-	    error = __mkSmallInteger(-2);
-	    goto err;
-	}
-
-	for (cnt = 0, addrpp = hp->h_addr_list; *addrpp; addrpp++)
-	    cnt++;
-	addrpp = hp->h_addr_list;
+        if (__isSmallInteger(domain) && hp->h_addrtype != __smallIntegerVal(domain)) {
+            errorString = @symbol(unknownHost);
+            error = __mkSmallInteger(-2);
+            goto err;
+        }
+
+        for (cnt = 0, addrpp = hp->h_addr_list; *addrpp; addrpp++)
+            cnt++;
+        addrpp = hp->h_addr_list;
     } else {
-	cnt = 1;
+        cnt = 1;
     }
 
     result = __ARRAY_NEW_INT(cnt);
     if (result == nil) {
-	error = @symbol(allocationFailure);
-	goto err;
+        error = @symbol(allocationFailure);
+        goto err;
     }
 
     for (i = 0; i < cnt; i++) {
-	OBJ o, resp;
-	struct sockaddr_in *sa;
-
-	resp = __ARRAY_NEW_INT(6);
-	if (resp == nil) {
-	    error = @symbol(allocationFailure);
-	    goto err;
-	}
-
-	__ArrayInstPtr(result)->a_element[i] = resp; __STORE(result, resp);
-	__ArrayInstPtr(resp)->a_element[0] = __mkSmallInteger(0);
-	__ArrayInstPtr(resp)->a_element[2] = type; __STORE(result, type);
-	__ArrayInstPtr(resp)->a_element[3] = proto; __STORE(result, proto);
-	__PROTECT__(resp);
-	o = __BYTEARRAY_NEW_INT(sizeof(*sa));
-	__UNPROTECT__(resp);
-	if (o == nil) {
-	    error = @symbol(allocationFailure);
-	    goto err;
-	}
-	__ArrayInstPtr(resp)->a_element[4] = o; __STORE(resp, o);
-	sa = (struct sockaddr_in *)__byteArrayVal(o);
-	sa->sin_port = port;
-
-	if (__hostName) {
-	    sa->sin_family = hp->h_addrtype;
-	    memcpy(&sa->sin_addr, *addrpp, hp->h_length);
-	    __ArrayInstPtr(resp)->a_element[1] = __mkSmallInteger(hp->h_addrtype);
-	    if (hp->h_name) {
-		__PROTECT__(resp);
-		o = __MKSTRING(hp->h_name);
-		__UNPROTECT__(resp);
-		if (o == nil) {
-		    error = @symbol(allocationFailure);
-		    goto err;
-		}
-		__ArrayInstPtr(resp)->a_element[5] = o; __STORE(resp, o);
-	    }
-	    addrpp++;
-	} else{
-	    __ArrayInstPtr(resp)->a_element[1] = domain; __STORE(resp, domain);
-	}
+        OBJ o, resp;
+        struct sockaddr_in *sa;
+
+        resp = __ARRAY_NEW_INT(6);
+        if (resp == nil) {
+            error = @symbol(allocationFailure);
+            goto err;
+        }
+
+        __ArrayInstPtr(result)->a_element[i] = resp; __STORE(result, resp);
+        __ArrayInstPtr(resp)->a_element[0] = __mkSmallInteger(0);
+        __ArrayInstPtr(resp)->a_element[2] = type; __STORE(result, type);
+        __ArrayInstPtr(resp)->a_element[3] = proto; __STORE(result, proto);
+        __PROTECT__(resp);
+        o = __BYTEARRAY_NEW_INT(sizeof(*sa));
+        __UNPROTECT__(resp);
+        if (o == nil) {
+            error = @symbol(allocationFailure);
+            goto err;
+        }
+        __ArrayInstPtr(resp)->a_element[4] = o; __STORE(resp, o);
+        sa = (struct sockaddr_in *)__byteArrayVal(o);
+        sa->sin_port = port;
+
+        if (__hostName) {
+            sa->sin_family = hp->h_addrtype;
+            memcpy(&sa->sin_addr, *addrpp, hp->h_length);
+            __ArrayInstPtr(resp)->a_element[1] = __mkSmallInteger(hp->h_addrtype);
+            if (hp->h_name) {
+                __PROTECT__(resp);
+                o = __MKSTRING(hp->h_name);
+                __UNPROTECT__(resp);
+                if (o == nil) {
+                    error = @symbol(allocationFailure);
+                    goto err;
+                }
+                __ArrayInstPtr(resp)->a_element[5] = o; __STORE(resp, o);
+            }
+            addrpp++;
+        } else{
+            __ArrayInstPtr(resp)->a_element[1] = domain; __STORE(resp, domain);
+        }
     }
 
 err:;
@@ -13632,10 +13638,10 @@
 out:;
 %}.
     error notNil ifTrue:[
-	errorString notNil ifTrue:[
-	    ^ errorString.
-	].
-	^ error.
+        errorString notNil ifTrue:[
+            ^ errorString.
+        ].
+        ^ error.
     ].
     ^ result.
 ! !
@@ -13658,49 +13664,49 @@
     int alen;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     if (peerOrNil != nil &&
-	(!__isNonNilObject(peerOrNil) ||
-	 (__intVal(__ClassInstPtr(__qClass(peerOrNil))->c_flags) & ARRAYMASK) != BYTEARRAY)) {
-	error = @symbol(badArgument2);
-	goto err;
+        (!__isNonNilObject(peerOrNil) ||
+         (__intVal(__ClassInstPtr(__qClass(peerOrNil))->c_flags) & ARRAYMASK) != BYTEARRAY)) {
+        error = @symbol(badArgument2);
+        goto err;
     }
 
     sock = __smallIntegerVal(__INST(fd));
 
 again:
     if (peerOrNil == nil) {
-	alen = 0;
-	sap = 0;
+        alen = 0;
+        sap = 0;
     } else {
-	alen =  __byteArraySize(peerOrNil);
-	sap = (struct sockaddr *)__byteArrayVal(peerOrNil);
+        alen =  __byteArraySize(peerOrNil);
+        sap = (struct sockaddr *)__byteArrayVal(peerOrNil);
     }
     newSock = accept(sock, sap, &alen);
     if (newSock < 0) {
-	switch (errno) {
-	case EINTR:
-	    __HANDLE_INTERRUPTS__;
-	    goto again;
+        switch (errno) {
+        case EINTR:
+            __HANDLE_INTERRUPTS__;
+            goto again;
 
 #ifdef EWOULDBLOCK
-	case EWOULDBLOCK:
+        case EWOULDBLOCK:
 # if defined(EAGAIN) && (EAGAIN != EWOULDBLOCK)
-	case EAGAIN:
+        case EAGAIN:
 # endif
 #else
 # ifdef EAGAIN
-	case EAGAIN:
-# endif
-#endif
-	    RETURN(nil);
-
-	default:
-	    error = __mkSmallInteger(errno);
-	    goto err;
-	}
+        case EAGAIN:
+# endif
+#endif
+            RETURN(nil);
+
+        default:
+            error = __mkSmallInteger(errno);
+            goto err;
+        }
     }
     newFd = __mkSmallInteger(newSock);
 
@@ -13708,7 +13714,7 @@
 #endif /* not NO_SOCKET */
 %}.
     error notNil ifTrue:[
-	^ self error:error.
+        ^ self error:error.
     ].
     ^ self class for:newFd
 ! !
@@ -13728,13 +13734,13 @@
     int ret;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     if (!__isNonNilObject(socketAddress) ||
-	(__intVal(__ClassInstPtr(__qClass(socketAddress))->c_flags) & ARRAYMASK) != BYTEARRAY) {
-	error = @symbol(badArgument1);
-	goto err;
+        (__intVal(__ClassInstPtr(__qClass(socketAddress))->c_flags) & ARRAYMASK) != BYTEARRAY) {
+        error = @symbol(badArgument1);
+        goto err;
     }
     sockaddr_size = __byteArraySize(socketAddress);
     sock = __smallIntegerVal(__INST(fd));
@@ -13742,27 +13748,27 @@
 again:
     ret = bind(sock, (struct sockaddr *)__byteArrayVal(socketAddress), sockaddr_size);
     if (ret < 0) {
-	if (errno == EINTR) {
-	    __HANDLE_INTERRUPTS__;
-	    goto again;
-	} else {
-	    error = __mkSmallInteger(errno);
-	    goto err;
-	}
+        if (errno == EINTR) {
+            __HANDLE_INTERRUPTS__;
+            goto again;
+        } else {
+            error = __mkSmallInteger(errno);
+            goto err;
+        }
     }
 
     err:;
 #endif /* NO_SOCKET */
 %}.
     error notNil ifTrue:[
-	^ self error:error.
+        ^ self error:error.
     ].
     ^ nil
 
     "
      (Socket domain:#inet type:#stream)
-	 bindTo:(IPSocketAddress hostAddress:IPSocketAddress anyAddress port:9999)
-	 reuseAddress:false ;
+         bindTo:(IPSocketAddress hostAddress:IPSocketAddress anyAddress port:9999)
+         reuseAddress:false ;
      yourself
     "
 ! !
@@ -13781,8 +13787,8 @@
     struct sockaddr sockaddr;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     sock = __smallIntegerVal(__INST(fd));
 
@@ -13794,17 +13800,17 @@
     ret = connect(sock, &sockaddr, sizeof(sockaddr));
     if (ret < 0) {
        switch(errno) {
-	   case EINTR:
+           case EINTR:
 # ifdef EAGAIN
-	    case EAGAIN:
-# endif
-		__HANDLE_INTERRUPTS__;
-		goto again;
-
-	    default:
-		error = __mkSmallInteger(errno);
-		break;
-	}
+            case EAGAIN:
+# endif
+                __HANDLE_INTERRUPTS__;
+                goto again;
+
+            default:
+                error = __mkSmallInteger(errno);
+                break;
+        }
     }
 
 err:;
@@ -13812,7 +13818,7 @@
 %}.
 
     error notNil ifTrue:[
-	^ self error:error.
+        ^ self error:error.
     ].
 !
 
@@ -13831,13 +13837,13 @@
     int sockaddr_size;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     if (!__isNonNilObject(socketAddress) ||
-	(__intVal(__ClassInstPtr(__qClass(socketAddress))->c_flags) & ARRAYMASK) != BYTEARRAY) {
-	error = @symbol(badArgument1);
-	goto err;
+        (__intVal(__ClassInstPtr(__qClass(socketAddress))->c_flags) & ARRAYMASK) != BYTEARRAY) {
+        error = @symbol(badArgument1);
+        goto err;
     }
     sock = __smallIntegerVal(__INST(fd));
     sockaddr_size = __qSize(socketAddress);
@@ -13845,47 +13851,47 @@
 again:
     ret = connect(sock, (struct sockaddr *)__byteArrayVal(socketAddress), sockaddr_size);
     if (ret >= 0) {
-	RETURN(true)
+        RETURN(true)
     }
 
     switch(errno) {
-	case EINTR:
+        case EINTR:
 # ifdef EAGAIN
-	case EAGAIN:
-# endif
-	    __HANDLE_INTERRUPTS__;
-	    goto again;
+        case EAGAIN:
+# endif
+            __HANDLE_INTERRUPTS__;
+            goto again;
 
 # if defined(EINPROGRESS) || defined(EALREADY)
 #  ifdef EINPROGRESS
-	case EINPROGRESS:
+        case EINPROGRESS:
 #  endif
 #  ifdef EALREADY
-	case EALREADY:
-#  endif
-	    RETURN(false);
+        case EALREADY:
+#  endif
+            RETURN(false);
 # endif
 
     default:
-	error = __mkSmallInteger(errno);
-	break;
+        error = __mkSmallInteger(errno);
+        break;
     }
 
 err:;
 #endif /* NO_SOCKET */
 %}.
     error notNil ifTrue:[
-	 ^ self error:error.
+         ^ self error:error.
     ].
     ^ true
 
     "
      Socket newTCP connectTo:(IPSocketAddress hostAddress:IPSocketAddress local port:7)
-		   withTimeout:nil.
+                   withTimeout:nil.
      Socket newTCP connectTo:(IPSocketAddress hostAddress:IPSocketAddress local port:5768)
-		   withTimeout:nil.
+                   withTimeout:nil.
      Socket newTCP connectTo:(IPSocketAddress hostAddress:#[1 2 3 4] port:7)
-		   withTimeout:nil.
+                   withTimeout:nil.
     "
 ! !
 
@@ -13915,46 +13921,46 @@
     int __flags, __startIndex, __nBytes;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     if (!__isSmallInteger(startIndex) ||
-	(__startIndex = __intVal(startIndex)-1) < 0) {
-	if (startIndex == nil) {
-	    __startIndex = 0;
-	} else {
-	    error = @symbol(badArgument3);
-	    goto err;
-	}
+        (__startIndex = __intVal(startIndex)-1) < 0) {
+        if (startIndex == nil) {
+            __startIndex = 0;
+        } else {
+            error = @symbol(badArgument3);
+            goto err;
+        }
     }
     if (__isSmallInteger(nBytes)) {
-	__nBytes = __intVal(nBytes);
+        __nBytes = __intVal(nBytes);
     } else if (nBytes == nil) {
-	__nBytes = -1;
+        __nBytes = -1;
     } else {
-	error = @symbol(badArgument4);
-	goto err;
+        error = @symbol(badArgument4);
+        goto err;
     }
     if (!__isInteger(flags)) {
-	error = @symbol(badArgument5);
-	goto err;
+        error = @symbol(badArgument5);
+        goto err;
     }
     __flags = __longIntVal(flags);
     sock = __smallIntegerVal(__INST(fd));
 
     oClass = __Class(aDataBuffer);
     switch (__intVal(__ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
-	case BYTEARRAY:
-	case WORDARRAY:
-	case SWORDARRAY:
-	case LONGARRAY:
-	case SLONGARRAY:
-	case FLOATARRAY:
-	case DOUBLEARRAY:
-	    break;
-	default:
-	    error = @symbol(badArgument2);
-	    goto err;
+        case BYTEARRAY:
+        case WORDARRAY:
+        case SWORDARRAY:
+        case LONGARRAY:
+        case SLONGARRAY:
+        case FLOATARRAY:
+        case DOUBLEARRAY:
+            break;
+        default:
+            error = @symbol(badArgument2);
+            goto err;
     }
 
     nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
@@ -13964,35 +13970,35 @@
     objSize -= __startIndex;
 
     if (__nBytes >= 0 &&__nBytes < objSize) {
-	objSize = __nBytes;
+        objSize = __nBytes;
     }
 
     if (socketAddress == nil) {
-	alen0 = 0;
+        alen0 = 0;
     } else {
-	if (!__isNonNilObject(socketAddress) ||
-	    (__intVal(__ClassInstPtr(__qClass(socketAddress))->c_flags) & ARRAYMASK) != BYTEARRAY) {
-	    error = @symbol(badArgument1);
-	    goto err;
-	}
-	alen0 = __byteArraySize(socketAddress);
+        if (!__isNonNilObject(socketAddress) ||
+            (__intVal(__ClassInstPtr(__qClass(socketAddress))->c_flags) & ARRAYMASK) != BYTEARRAY) {
+            error = @symbol(badArgument1);
+            goto err;
+        }
+        alen0 = __byteArraySize(socketAddress);
     }
     saPtr = (struct sockaddr *)0;
 
 again:
     alen = alen0;
     if (alen)
-	saPtr = (struct sockaddr *)__byteArrayVal(socketAddress);
+        saPtr = (struct sockaddr *)__byteArrayVal(socketAddress);
     cp = (char *)__InstPtr(aDataBuffer) + nInstBytes;
     n = recvfrom(sock, cp, objSize, __flags, saPtr, &alen);
     if (n < 0) {
-	if (errno == EINTR) {
-	    __HANDLE_INTERRUPTS__;
-	    goto again;
-	} else {
-	    error = __mkSmallInteger(errno);
-	    goto err;
-	}
+        if (errno == EINTR) {
+            __HANDLE_INTERRUPTS__;
+            goto again;
+        } else {
+            error = __mkSmallInteger(errno);
+            goto err;
+        }
     }
     RETURN (__mkSmallInteger(n));
 #endif
@@ -14022,65 +14028,65 @@
     int offs, __startIndex, __maxBytes;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     if (!__isSmallInteger(startIndex) ||
-	(__startIndex = __intVal(startIndex)-1) < 0) {
-	if (startIndex == nil) {
-	    __startIndex = 0;
-	} else {
-	    error = @symbol(badArgument3);
-	    goto err;
-	}
+        (__startIndex = __intVal(startIndex)-1) < 0) {
+        if (startIndex == nil) {
+            __startIndex = 0;
+        } else {
+            error = @symbol(badArgument3);
+            goto err;
+        }
     }
     if (__isSmallInteger(maxBytes)) {
-	__maxBytes = __intVal(maxBytes);
+        __maxBytes = __intVal(maxBytes);
     } else if (maxBytes == nil) {
-	__maxBytes = -1;
+        __maxBytes = -1;
     } else {
-	error = @symbol(badArgument4);
-	goto err;
+        error = @symbol(badArgument4);
+        goto err;
     }
     if (!__isInteger(flags)) {
-	error = @symbol(badArgument5);
-	goto err;
+        error = @symbol(badArgument5);
+        goto err;
     }
     __flags = __longIntVal(flags);
     sock = __smallIntegerVal(__INST(fd));
 
     oClass = __Class(aDataBuffer);
     switch (__intVal(__ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
-	case BYTEARRAY:
-	    offs = __startIndex;
-	    break;
-	case WORDARRAY:
-	case SWORDARRAY:
-	    offs = __startIndex * 2;
-	    break;
-	case LONGARRAY:
-	case SLONGARRAY:
-	    offs = __startIndex * 4;
-	    break;
-	case LONGLONGARRAY:
-	case SLONGLONGARRAY:
-	    offs = __startIndex * 8;
+        case BYTEARRAY:
+            offs = __startIndex;
+            break;
+        case WORDARRAY:
+        case SWORDARRAY:
+            offs = __startIndex * 2;
+            break;
+        case LONGARRAY:
+        case SLONGARRAY:
+            offs = __startIndex * 4;
+            break;
+        case LONGLONGARRAY:
+        case SLONGLONGARRAY:
+            offs = __startIndex * 8;
 # ifdef __NEED_LONGLONG_ALIGN
-	    offs += 4;
-# endif
-	    break;
-	case FLOATARRAY:
-	    offs = __startIndex * sizeof(float);
-	    break;
-	case DOUBLEARRAY:
-	    offs = __startIndex * sizeof(double);
+            offs += 4;
+# endif
+            break;
+        case FLOATARRAY:
+            offs = __startIndex * sizeof(float);
+            break;
+        case DOUBLEARRAY:
+            offs = __startIndex * sizeof(double);
 # ifdef __NEED_DOUBLE_ALIGN
-	    offs += 4;
-# endif
-	    break;
-	default:
-	    error = @symbol(badArgument2);
-	    goto err;
+            offs += 4;
+# endif
+            break;
+        default:
+            error = @symbol(badArgument2);
+            goto err;
     }
 
     nInstVars = __smallIntegerVal(__ClassInstPtr(oClass)->c_ninstvars);
@@ -14089,35 +14095,35 @@
 
     if (__maxBytes >= 0 && __maxBytes < objSize) {
 # ifdef DGRAM_DEBUG
-	printf("cut off ...\n");
-# endif
-	objSize = __maxBytes;
+        printf("cut off ...\n");
+# endif
+        objSize = __maxBytes;
     }
 
     if (socketAddress == nil) {
-	alen = 0;
+        alen = 0;
     } else {
-	if (! __isByteArrayLike(socketAddress)) {
-	    error = @symbol(badArgument1);
-	    goto err;
-	}
-	alen = __byteArraySize(socketAddress);
+        if (! __isByteArrayLike(socketAddress)) {
+            error = @symbol(badArgument1);
+            goto err;
+        }
+        alen = __byteArraySize(socketAddress);
     }
     saPtr = (struct sockaddr *)0;
 
 again:
     if (alen)
-	saPtr = (struct sockaddr *)__byteArrayVal(socketAddress);
+        saPtr = (struct sockaddr *)__byteArrayVal(socketAddress);
     cp = (char *)__InstPtr(aDataBuffer) + nInstBytes + offs;
     n = sendto(sock, cp, objSize, __flags, saPtr, alen);
     if (n < 0) {
-	if (errno == EINTR) {
-	    __HANDLE_INTERRUPTS__;
-	    goto again;
-	} else {
-	    error = __mkSmallInteger(errno);
-	    goto err;
-	}
+        if (errno == EINTR) {
+            __HANDLE_INTERRUPTS__;
+            goto again;
+        } else {
+            error = __mkSmallInteger(errno);
+            goto err;
+        }
     }
     RETURN (__mkSmallInteger(n));
 #endif
@@ -14142,7 +14148,7 @@
     domainCode := OperatingSystem domainCodeOf:domainArg.
     typeCode := OperatingSystem socketTypeCodeOf:typeArg.
     protocolArg notNil ifTrue:[
-	protocolNumber := self class protocolCodeOf:protocolArg
+        protocolNumber := self class protocolCodeOf:protocolArg
     ].
 
 %{
@@ -14151,23 +14157,23 @@
     int on = 1;
 
     if (__INST(fd) != nil) {
-	error = @symbol(internalError);
-	goto err;
+        error = @symbol(internalError);
+        goto err;
     }
     if (! __isSmallInteger(domainCode)) {
-	error = @symbol(badArgument1);
-	goto err;
+        error = @symbol(badArgument1);
+        goto err;
     }
     if (! __isSmallInteger(typeArg)) {
-	error = @symbol(badArgument2);
-	goto err;
+        error = @symbol(badArgument2);
+        goto err;
     }
     if (protocolNumber != nil) {
-	if (!__isSmallInteger(protocolNumber)) {
-	    error = @symbol(badArgument3);
-	    goto err;
-	}
-	proto = __smallIntegerVal(protocolNumber);
+        if (!__isSmallInteger(protocolNumber)) {
+            error = @symbol(badArgument3);
+            goto err;
+        }
+        proto = __smallIntegerVal(protocolNumber);
     }
     dom = __smallIntegerVal(domainCode);
 
@@ -14179,20 +14185,20 @@
 againSocket:
     sock = socket(dom, typ, proto);
     if (sock < 0) {
-	if (errno == EINTR) {
-	    __HANDLE_INTERRUPTS__;
-	    goto againSocket;
-	} else
+        if (errno == EINTR) {
+            __HANDLE_INTERRUPTS__;
+            goto againSocket;
+        } else
 # if defined(EPROTONOSUPPORT) /* for SGI */
-	if (errno == EPROTONOSUPPORT && proto != 0) {
-	    proto = 0;
-	    goto againSocket;
-	} else
-# endif
-	{
-	    error = __mkSmallInteger(errno);
-	    goto err;
-	}
+        if (errno == EPROTONOSUPPORT && proto != 0) {
+            proto = 0;
+            goto againSocket;
+        } else
+# endif
+        {
+            error = __mkSmallInteger(errno);
+            goto err;
+        }
     }
     __INST(fd) = __mkSmallInteger(sock);
 
@@ -14202,7 +14208,7 @@
 # endif /* NOSOCKET */
 %}.
     error notNil ifTrue:[
-	^ self error:error.
+        ^ self error:error.
     ].
     self register.
 
@@ -14228,23 +14234,23 @@
     char *p;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     if (!__bothSmallInteger(level, name)) {
-	error = @symbol(badArgument);
-	goto err;
+        error = @symbol(badArgument);
+        goto err;
     }
     if (!__isByteArray(bytes)) {
-	error = @symbol(internalError);
-	goto err;
+        error = @symbol(internalError);
+        goto err;
     }
     p = __byteArrayVal(bytes);
     sz = __byteArraySize(bytes);
 
     sock = __smallIntegerVal(__INST(fd));
     if (getsockopt(sock, __smallIntegerVal(level), __smallIntegerVal(name), p, &sz) < 0) {
-	error = __mkSmallInteger(errno);
+        error = __mkSmallInteger(errno);
     }
     size = __mkSmallInteger(sz);
 
@@ -14252,7 +14258,7 @@
 #endif
 %}.
     error notNil ifTrue:[
-	^ self error:error
+        ^ self error:error
     ].
     ^ bytes copyTo:size
 !
@@ -14269,12 +14275,12 @@
     int sock, ret;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     if (!__isSmallInteger(aNumber)) {
-	error = @symbol(badArgument1);
-	goto err;
+        error = @symbol(badArgument1);
+        goto err;
     }
 
     sock = __smallIntegerVal(__INST(fd));
@@ -14282,19 +14288,19 @@
 again:
     ret = listen(sock, __smallIntegerVal(aNumber));
     if (ret < 0) {
-	if (errno == EINTR) {
-	    __HANDLE_INTERRUPTS__;
-	    goto again;
-	} else {
-	    error = __mkSmallInteger(errno);
-	}
+        if (errno == EINTR) {
+            __HANDLE_INTERRUPTS__;
+            goto again;
+        } else {
+            error = __mkSmallInteger(errno);
+        }
     }
 
 err:;
 #endif
 %}.
     error notNil ifTrue:[
-	^ self error:error.
+        ^ self error:error.
     ].
     ^ nil
 !
@@ -14312,48 +14318,48 @@
     char *p;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     if (__isSmallInteger(level)) {
-	__level = __smallIntegerVal(level);
+        __level = __smallIntegerVal(level);
     } else if (level == @symbol(SOL_SOCKET)) {
-	__level = SOL_SOCKET;
+        __level = SOL_SOCKET;
     } else {
-	error = @symbol(badArgument1);
-	goto err;
+        error = @symbol(badArgument1);
+        goto err;
     }
 
     if (__isSmallInteger(name)) {
-	__name = __smallIntegerVal(name);
+        __name = __smallIntegerVal(name);
     } else if (name == @symbol(SO_REUSEADDR)) {
-	__name = SO_REUSEADDR;
+        __name = SO_REUSEADDR;
     } else {
-	error = @symbol(badArgument2);
-	goto err;
+        error = @symbol(badArgument2);
+        goto err;
     }
 
     if (__isSmallInteger(value)) {
-	intval = __intVal(value);
-	p = (char *) &intval;
-	sz = sizeof(intval);
+        intval = __intVal(value);
+        p = (char *) &intval;
+        sz = sizeof(intval);
     } else if (__isByteArrayLike(value)) {
-	p = __byteArrayVal(value);
-	sz = __byteArraySize(value);
+        p = __byteArrayVal(value);
+        sz = __byteArraySize(value);
     } else {
-	error = @symbol(badArgument3);
-	goto err;
+        error = @symbol(badArgument3);
+        goto err;
     }
 
     sock = __smallIntegerVal(__INST(fd));
     if (setsockopt(sock, __level, __name, p, sz) < 0) {
-	error = __mkSmallInteger(errno);
+        error = __mkSmallInteger(errno);
     }
 err:;
 #endif
 %}.
     error notNil ifTrue:[
-	^ self error:error
+        ^ self error:error
     ].
     ^ nil.
 !
@@ -14363,9 +14369,9 @@
      anInteger == 0   no reads will be performed
      anInteger == 1   no writes will be performed
      anInteger == 2   neither reads nor writes will be performed.
-		      Pending data is discarded. This is faster tha
-		      close, which may wait until pending (written)
-		      data has been read by the other side"
+                      Pending data is discarded. This is faster tha
+                      close, which may wait until pending (written)
+                      data has been read by the other side"
 
     |error|
 
@@ -14374,30 +14380,30 @@
     int ret;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     if (!__isSmallInteger(anInteger)) {
-	error = @symbol(badArgument1);
-	goto err;
+        error = @symbol(badArgument1);
+        goto err;
     }
 
 again:
     ret = shutdown(__smallIntegerVal(__INST(fd)), __smallIntegerVal(anInteger));
     if (ret < 0) {
-	if (errno == EINTR) {
-	    __HANDLE_INTERRUPTS__;
-	    goto again;
-	} else {
-	    error = __mkSmallInteger(errno);
-	}
+        if (errno == EINTR) {
+            __HANDLE_INTERRUPTS__;
+            goto again;
+        } else {
+            error = __mkSmallInteger(errno);
+        }
     }
 
 err:;
 #endif /*NO_SOCKET*/
 %}.
     error notNil ifTrue:[
-	^ self error:error
+        ^ self error:error
     ].
     ^ nil.
 ! !
@@ -14417,26 +14423,26 @@
     int ret;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     if (!__isNonNilObject(socketAddress) ||
-	(__intVal(__ClassInstPtr(__qClass(socketAddress))->c_flags) & ARRAYMASK) != BYTEARRAY) {
-	error = @symbol(badArgument1);
-	goto err;
+        (__intVal(__ClassInstPtr(__qClass(socketAddress))->c_flags) & ARRAYMASK) != BYTEARRAY) {
+        error = @symbol(badArgument1);
+        goto err;
     }
     sockaddr_size = __byteArraySize(socketAddress);
 
     sock = __smallIntegerVal(__INST(fd));
     ret = getsockname(sock, (struct sockaddr *)__byteArrayVal(socketAddress), &sockaddr_size);
     if (ret < 0) {
-	error = __mkSmallInteger(errno);
+        error = __mkSmallInteger(errno);
     }
 err:;
 #endif /* NO_SOCKET */
 %}.
     error notNil ifTrue:[
-	^ self error:error
+        ^ self error:error
     ].
     ^ nil.
 !
@@ -14454,27 +14460,27 @@
     int __ret;
 
     if (!__isSmallInteger(__INST(fd))) {
-	error = @symbol(badFd);
-	goto err;
+        error = @symbol(badFd);
+        goto err;
     }
     if (!__isNonNilObject(socketAddress) ||
-	(__intVal(__ClassInstPtr(__qClass(socketAddress))->c_flags) & ARRAYMASK) != BYTEARRAY) {
-	error = @symbol(badArgument1);
-	goto err;
+        (__intVal(__ClassInstPtr(__qClass(socketAddress))->c_flags) & ARRAYMASK) != BYTEARRAY) {
+        error = @symbol(badArgument1);
+        goto err;
     }
     __sockaddr_size = __byteArraySize(socketAddress);
 
     __sock = __smallIntegerVal(__INST(fd));
     __ret = getpeername(__sock, (struct sockaddr *)__byteArrayVal(socketAddress),
-				&__sockaddr_size);
+                                &__sockaddr_size);
     if (__ret < 0) {
-	error = __mkSmallInteger(errno);
+        error = __mkSmallInteger(errno);
     }
 err:;
 #endif /* NO_SOCKET */
 %}.
     error notNil ifTrue:[
-	^ self error:error
+        ^ self error:error
     ].
     ^ nil
 ! !
--- a/WeakArray.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/WeakArray.st	Fri Jul 24 08:06:37 2015 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
@@ -507,7 +509,7 @@
 do:aBlock
     "evaluate the argument, aBlock for each element in the collection.
      - reimplemented for IGC readBarrier.
-     You dont have to understand this."
+     You don't have to understand this."
 
     |element|
 
@@ -521,50 +523,50 @@
 
     if (__isBlockLike(aBlock)
      && (__BlockInstPtr(aBlock)->b_nargs == __mkSmallInteger(1))) {
-	{
-	    /*
-	     * the most common case: a static compiled block, with home on the stack ...
-	     */
-	    REGISTER OBJFUNC codeVal;
+        {
+            /*
+             * the most common case: a static compiled block, with home on the stack ...
+             */
+            REGISTER OBJFUNC codeVal;
 
-	    if (((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
-	     && (! ((INT)(__BlockInstPtr(aBlock)->b_flags) & __MASKSMALLINT(F_DYNAMIC)))) {
+            if (((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
+             && (! ((INT)(__BlockInstPtr(aBlock)->b_flags) & __MASKSMALLINT(F_DYNAMIC)))) {
 
 #ifdef NEW_BLOCK_CALL
 #               define BLOCK_ARG        aBlock
 #else
 #               define BLOCK_ARG        rHome
-		REGISTER OBJ rHome;
+                REGISTER OBJ rHome;
 
-		rHome = __BlockInstPtr(aBlock)->b_home;
-		if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE))
+                rHome = __BlockInstPtr(aBlock)->b_home;
+                if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE))
 #endif
-		{
-		    for (; index < nIndex; index++) {
-			if (InterruptPending != nil) __interruptL(@line);
+                {
+                    for (; index < nIndex; index++) {
+                        if (InterruptPending != nil) __interruptL(@line);
 
-			element = __InstPtr(self)->i_instvars[index];
-			if (__isNonNilObject(element)) {
-			    element = __WEAK_READ__(self, element);
+                        element = __InstPtr(self)->i_instvars[index];
+                        if (__isNonNilObject(element)) {
+                            element = __WEAK_READ__(self, element);
 #ifdef WEAK_DEBUG
-			    if (! __ISVALIDOBJECT(element)) {
-				fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
-				__dumpObject__(element, __LINE__);
-				element = nil;
-			    }
+                            if (! __ISVALIDOBJECT(element)) {
+                                fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
+                                __dumpObject__(element, __LINE__);
+                                element = nil;
+                            }
 #endif
-			}
-			(*codeVal)(BLOCK_ARG, element);
-		    }
-		    RETURN (self);
-		}
-	    }
-	}
+                        }
+                        (*codeVal)(BLOCK_ARG, element);
+                    }
+                    RETURN (self);
+                }
+            }
+        }
 
-	/*
-	 * sorry, must check code-pointer in the loop
-	 * it could be recompiled or flushed
-	 */
+        /*
+         * sorry, must check code-pointer in the loop
+         * it could be recompiled or flushed
+         */
 #       undef BLOCK_ARG
 #ifdef NEW_BLOCK_CALL
 #       define BLOCK_ARG        aBlock
@@ -574,44 +576,44 @@
 #       define IBLOCK_ARG       (__BlockInstPtr(aBlock)->b_home)
 #endif
 
-	for (; index < nIndex; index++) {
-	    REGISTER OBJFUNC codeVal;
+        for (; index < nIndex; index++) {
+            REGISTER OBJFUNC codeVal;
 
-	    if (InterruptPending != nil) __interruptL(@line);
+            if (InterruptPending != nil) __interruptL(@line);
 
-	    element = __InstPtr(self)->i_instvars[index];
-	    if (__isNonNilObject(element)) {
-		element = __WEAK_READ__(self, element);
+            element = __InstPtr(self)->i_instvars[index];
+            if (__isNonNilObject(element)) {
+                element = __WEAK_READ__(self, element);
 #ifdef WEAK_DEBUG
-		if (! __ISVALIDOBJECT(element)) {
-		    fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
-		    __dumpObject__(element, __LINE__);
-		    element = nil;
-		}
+                if (! __ISVALIDOBJECT(element)) {
+                    fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
+                    __dumpObject__(element, __LINE__);
+                    element = nil;
+                }
 #endif
-	    }
-	    if ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil) {
-		(*codeVal)(BLOCK_ARG, element);
-	    } else {
-		if (__BlockInstPtr(aBlock)->b_bytecodes != nil) {
-		    /*
-		     * arg is a compiled block with bytecode -
-		     * directly call interpreter without going through Block>>value
-		     */
+            }
+            if ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil) {
+                (*codeVal)(BLOCK_ARG, element);
+            } else {
+                if (__BlockInstPtr(aBlock)->b_bytecodes != nil) {
+                    /*
+                     * arg is a compiled block with bytecode -
+                     * directly call interpreter without going through Block>>value
+                     */
 #ifdef PASS_ARG_POINTER
-		    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, &element);
+                    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, &element);
 #else
-		    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, element);
+                    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, element);
 #endif
-		} else {
-		    /*
-		     * arg is something else - call it with #value
-		     */
-		    (*val.ilc_func)(aBlock, @symbol(value:), nil, &val, element);
-		}
-	    }
-	}
-	RETURN (self);
+                } else {
+                    /*
+                     * arg is something else - call it with #value
+                     */
+                    (*val.ilc_func)(aBlock, @symbol(value:), nil, &val, element);
+                }
+            }
+        }
+        RETURN (self);
 
 #       undef BLOCK_ARG
 #       undef IBLOCK_ARG
@@ -622,29 +624,31 @@
      * not a block - send it #value:
      */
     for (; index < nIndex; index++) {
-	if (InterruptPending != nil) __interruptL(@line);
+        if (InterruptPending != nil) __interruptL(@line);
 
-	element = __InstPtr(self)->i_instvars[index];
-	if (__isNonNilObject(element)) {
-	    element = __WEAK_READ__(self, element);
+        element = __InstPtr(self)->i_instvars[index];
+        if (__isNonNilObject(element)) {
+            element = __WEAK_READ__(self, element);
 #ifdef WEAK_DEBUG
-	    if (! __ISVALIDOBJECT(element)) {
-		fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
-		__dumpObject__(element, __LINE__);
-		element = nil;
-	    }
+            if (! __ISVALIDOBJECT(element)) {
+                fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
+                __dumpObject__(element, __LINE__);
+                element = nil;
+            }
 #endif
-	}
-	(*val.ilc_func)(aBlock,
-			    @symbol(value:),
-			    nil, &val,
-			    element);
+        }
+        (*val.ilc_func)(aBlock,
+                            @symbol(value:),
+                            nil, &val,
+                            element);
     }
     RETURN (self);
 %}.
     ^ super do:[:each |
-	each ~~ nil ifTrue:[aBlock value:each]
+        each ~~ nil ifTrue:[aBlock value:each]
       ]
+
+    "Modified: / 23-07-2015 / 15:35:24 / cg"
 !
 
 forAllDeadIndicesDo:aBlock
@@ -847,7 +851,7 @@
 !
 
 validElementsDo:aBlock
-    "evaluate the argument, aBlock for each non-nil/non-zero element"
+    "evaluate the argument, aBlock for each non-nil/non-evacuated element"
 
     |element|
 %{
@@ -859,57 +863,57 @@
     nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
     if (__isBlockLike(aBlock)
      && (__BlockInstPtr(aBlock)->b_nargs == __mkSmallInteger(1))) {
-	{
-	    /*
-	     * the most common case: a static compiled block, with home on the stack ...
-	     */
-	    REGISTER OBJFUNC codeVal;
+        {
+            /*
+             * the most common case: a static compiled block, with home on the stack ...
+             */
+            REGISTER OBJFUNC codeVal;
 
-	    if (((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
-	     && (! ((INT)(__BlockInstPtr(aBlock)->b_flags) & __MASKSMALLINT(F_DYNAMIC)))) {
+            if (((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
+             && (! ((INT)(__BlockInstPtr(aBlock)->b_flags) & __MASKSMALLINT(F_DYNAMIC)))) {
 
 #ifdef NEW_BLOCK_CALL
 #               define BLOCK_ARG        aBlock
 #else
 #               define BLOCK_ARG        rHome
-		REGISTER OBJ rHome;
+                REGISTER OBJ rHome;
 
-		rHome = __BlockInstPtr(aBlock)->b_home;
-		if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE))
+                rHome = __BlockInstPtr(aBlock)->b_home;
+                if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE))
 #endif
-		{
-		    for (; index < nIndex; index++) {
-			element = __InstPtr(self)->i_instvars[index];
-			if (element && (element != __mkSmallInteger(0))) {
-			    if (InterruptPending != nil) {
-				__interruptL(@line);
-				element = __InstPtr(self)->i_instvars[index];
-			    }
+                {
+                    for (; index < nIndex; index++) {
+                        element = __InstPtr(self)->i_instvars[index];
+                        if (__isNonNilObject(element)) {
+                            if (InterruptPending != nil) {
+                                __interruptL(@line);
+                                element = __InstPtr(self)->i_instvars[index];
+                            }
 
-			    if (__isNonNilObject(element)) {
-				element = __WEAK_READ__(self, element);
+                            if (__isNonNilObject(element)) {
+                                element = __WEAK_READ__(self, element);
 #ifdef WEAK_DEBUG
-				if (! __ISVALIDOBJECT(element)) {
-				    fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
-				    __dumpObject__(element, __LINE__);
-				    element = nil;
-				}
+                                if (! __ISVALIDOBJECT(element)) {
+                                    fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
+                                    __dumpObject__(element, __LINE__);
+                                    element = nil;
+                                }
 #endif
-			    }
-			    if (element && (element != __mkSmallInteger(0))) {
-				(*codeVal)(BLOCK_ARG, element);
-			    }
-			}
-		    }
-		    RETURN (self);
-		}
-	    }
-	}
+                                if (__isNonNilObject(element)) {
+                                    (*codeVal)(BLOCK_ARG, element);
+                                }
+                            }
+                        }
+                    }
+                    RETURN (self);
+                }
+            }
+        }
 
-	/*
-	 * sorry, must check code-pointer in the loop
-	 * it could be recompiled or flushed
-	 */
+        /*
+         * sorry, must check code-pointer in the loop
+         * it could be recompiled or flushed
+         */
 #       undef BLOCK_ARG
 #ifdef NEW_BLOCK_CALL
 #       define BLOCK_ARG        aBlock
@@ -919,50 +923,50 @@
 #       define IBLOCK_ARG       (__BlockInstPtr(aBlock)->b_home)
 #endif
 
-	for (; index < nIndex; index++) {
-	    REGISTER OBJFUNC codeVal;
+        for (; index < nIndex; index++) {
+            REGISTER OBJFUNC codeVal;
 
-	    element = __InstPtr(self)->i_instvars[index];
-	    if (element && (element != __mkSmallInteger(0))) {
-		if (InterruptPending != nil) {
-		    __interruptL(@line);
-		    element = __InstPtr(self)->i_instvars[index];
-		}
-		if (__isNonNilObject(element)) {
-		    element = __WEAK_READ__(self, element);
+            element = __InstPtr(self)->i_instvars[index];
+            if (__isNonNilObject(element)) {
+                if (InterruptPending != nil) {
+                    __interruptL(@line);
+                    element = __InstPtr(self)->i_instvars[index];
+                }
+                if (__isNonNilObject(element)) {
+                    element = __WEAK_READ__(self, element);
 #ifdef WEAK_DEBUG
-		    if (! __ISVALIDOBJECT(element)) {
-			fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
-			__dumpObject__(element, __LINE__);
-			element = nil;
-		    }
+                    if (! __ISVALIDOBJECT(element)) {
+                        fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
+                        __dumpObject__(element, __LINE__);
+                        element = nil;
+                    }
 #endif
-		}
-		if (element && (element != __mkSmallInteger(0))) {
-		    if ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil) {
-			(*codeVal)(BLOCK_ARG, element);
-		    } else {
-			if (__BlockInstPtr(aBlock)->b_bytecodes != nil) {
-			    /*
-			     * arg is a compiled block with bytecode -
-			     * directly call interpreter without going through Block>>value
-			     */
+                    if (__isNonNilObject(element)) {
+                        if ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil) {
+                            (*codeVal)(BLOCK_ARG, element);
+                        } else {
+                            if (__BlockInstPtr(aBlock)->b_bytecodes != nil) {
+                                /*
+                                 * arg is a compiled block with bytecode -
+                                 * directly call interpreter without going through Block>>value
+                                 */
 #ifdef PASS_ARG_POINTER
-			    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, &element);
+                                __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, &element);
 #else
-			    __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, element);
+                                __interpret(aBlock, 1, nil, IBLOCK_ARG, nil, nil, element);
 #endif
-			} else {
-			    /*
-			     * arg is something else - call it with #value
-			     */
-			    (*val.ilc_func)(aBlock, @symbol(value:), nil, &val, element);
-			}
-		    }
-		}
-	    }
-	}
-	RETURN (self);
+                            } else {
+                                /*
+                                 * arg is something else - call it with #value
+                                 */
+                                (*val.ilc_func)(aBlock, @symbol(value:), nil, &val, element);
+                            }
+                        }
+                    }
+                }
+            }
+        }
+        RETURN (self);
 
 #       undef BLOCK_ARG
 #       undef IBLOCK_ARG
@@ -972,36 +976,37 @@
      * not a block - send it #value:
      */
     for (; index < nIndex; index++) {
-	element = __InstPtr(self)->i_instvars[index];
-	if (element && (element != __mkSmallInteger(0))) {
-	    if (InterruptPending != nil) {
-		__interruptL(@line);
-		element = __InstPtr(self)->i_instvars[index];
-	    }
-	    if (__isNonNilObject(element)) {
-		element = __WEAK_READ__(self, element);
+        element = __InstPtr(self)->i_instvars[index];
+        if (__isNonNilObject(element)) {
+            if (InterruptPending != nil) {
+                __interruptL(@line);
+                element = __InstPtr(self)->i_instvars[index];
+            }
+            if (__isNonNilObject(element)) {
+                element = __WEAK_READ__(self, element);
 #ifdef WEAK_DEBUG
-		if (! __ISVALIDOBJECT(element)) {
-		    fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
-		    __dumpObject__(element, __LINE__);
-		    element = nil;
-		}
+                if (! __ISVALIDOBJECT(element)) {
+                    fprintf(stderr, "****** OOPS - invalid Weak-Read\n");
+                    __dumpObject__(element, __LINE__);
+                    element = nil;
+                }
 #endif
-	    }
-	    if (element && (element != __mkSmallInteger(0))) {
-		(*val.ilc_func)(aBlock,
-				    @symbol(value:),
-				    nil, &val,
-				    element);
-	    }
-	}
+                if (__isNonNilObject(element)) {
+                    (*val.ilc_func)(aBlock,
+                                    @symbol(value:),
+                                    nil, &val,
+                                    element);
+                }
+            }
+        }
     }
     RETURN (self);
 %}.
     ^ super do:[:each |
-	(each ~~ nil and:[each ~~ 0]) ifTrue:[aBlock value:each]
+        (each ~~ nil and:[each class ~~ SmallInteger]) ifTrue:[aBlock value:each]
       ]
 
+    "Modified: / 23-07-2015 / 15:32:44 / cg"
 ! !
 
 !WeakArray methodsFor:'notification'!
--- a/WeakDependencyDictionary.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/WeakDependencyDictionary.st	Fri Jul 24 08:06:37 2015 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1997 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
@@ -23,7 +23,7 @@
 copyright
 "
  COPYRIGHT (c) 1997 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -42,10 +42,10 @@
     dependency mechanism.
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [See also:]
-        WeakArray WeakIdentityDictionary WeakValueDictionary WeakIdentitySet
+	WeakArray WeakIdentityDictionary WeakValueDictionary WeakIdentitySet
 "
 ! !
 
@@ -79,48 +79,48 @@
 
     index := 1.
     [index <= keyArray size] whileTrue:[
-        "/ get the size again - it could have changed
+	"/ get the size again - it could have changed
 
-        wasBlocked := OperatingSystem blockInterrupts.
+	wasBlocked := OperatingSystem blockInterrupts.
 
-        keyArray ~~ originalKeyArray ifTrue:[
-            index := 1. "/ start over
-            "/ 'restart removeEmpty' infoPrintCR.
-            originalKeyArray := keyArray.
-        ].
+	keyArray ~~ originalKeyArray ifTrue:[
+	    index := 1. "/ start over
+	    "/ 'restart removeEmpty' infoPrintCR.
+	    originalKeyArray := keyArray.
+	].
 
-        index <= keyArray size ifTrue:[
-            key := keyArray basicAt:index.
-            key == 0 ifTrue:[
-                "/ that one is gone
-                key := DeletedEntry.
-                keyArray basicAt:index put:key.
-                valueArray basicAt:index put:nil.
-                tally := tally - 1.
-            ].
+	index <= keyArray size ifTrue:[
+	    key := keyArray basicAt:index.
+	    key class == SmallInteger ifTrue:[
+		"/ that one is gone
+		key := DeletedEntry.
+		keyArray basicAt:index put:key.
+		valueArray basicAt:index put:nil.
+		tally := tally - 1.
+	    ].
 
-            (key notNil and:[key ~~ DeletedEntry]) ifTrue:[
-                deps := valueArray basicAt:index.
-                deps notNil ifTrue:[
-                    "/ is it an empty WeakArray ?
+	    (key notNil and:[key ~~ DeletedEntry]) ifTrue:[
+		deps := valueArray basicAt:index.
+		deps notNil ifTrue:[
+		    "/ is it an empty WeakArray ?
 
-                    (deps isMemberOf:WeakArray) ifTrue:[
-                        t := deps findFirst:[:el | el notNil and:[el ~~ 0]].
-                        t == 0 ifTrue:[
-                            "/ yes - nil it
-                            valueArray basicAt:index put:nil.
-                            keyArray basicAt:index put:DeletedEntry.
-                            tally := tally - 1.
-                        ]
-                    ] ifFalse:[
-                       "/ is it an empty WeakIdSet ?
+		    (deps isMemberOf:WeakArray) ifTrue:[
+			t := deps findFirst:[:el | el notNil and:[el ~~ 0]].
+			t == 0 ifTrue:[
+			    "/ yes - nil it
+			    valueArray basicAt:index put:nil.
+			    keyArray basicAt:index put:DeletedEntry.
+			    tally := tally - 1.
+			]
+		    ] ifFalse:[
+		       "/ is it an empty WeakIdSet ?
 
-                       (deps isMemberOf:WeakIdentitySet) ifTrue:[
-                            (t := deps size) == 0 ifTrue:[
-                                "/ yes - nil it
-                                valueArray basicAt:index put:nil.
-                                keyArray basicAt:index put:DeletedEntry.
-                                tally := tally - 1.
+		       (deps isMemberOf:WeakIdentitySet) ifTrue:[
+			    (t := deps size) == 0 ifTrue:[
+				"/ yes - nil it
+				valueArray basicAt:index put:nil.
+				keyArray basicAt:index put:DeletedEntry.
+				tally := tally - 1.
 "/                            ] ifFalse:[
 "/                                t == 1 ifTrue:[
 "/                                    "/ careful - it could actually be empty
@@ -136,19 +136,19 @@
 "/                                        ]
 "/                                    ]
 "/                                ]
-                            ]
-                        ]
-                    ]
-                ] ifFalse:[
-                    "/ 'oops: nil value for key' infoPrint. key infoPrintCR.
-                    keyArray basicAt:index put:DeletedEntry.
-                    tally := tally - 1.
-                ]
-            ]
-        ].
+			    ]
+			]
+		    ]
+		] ifFalse:[
+		    "/ 'oops: nil value for key' infoPrint. key infoPrintCR.
+		    keyArray basicAt:index put:DeletedEntry.
+		    tally := tally - 1.
+		]
+	    ]
+	].
 
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-        index := index + 1.
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	index := index + 1.
     ].
 
 "/ 'done' printCR.
@@ -163,5 +163,5 @@
 !WeakDependencyDictionary class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/WeakDependencyDictionary.st,v 1.14 2012-08-06 12:38:10 cg Exp $'
+    ^ '$Header$'
 ! !
--- a/WeakIdentityDictionary.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/WeakIdentityDictionary.st	Fri Jul 24 08:06:37 2015 +0100
@@ -40,8 +40,8 @@
 
 documentation
 "
-    WeakIdentityDictionaries behave like IdentityDictionaries, 
-    as long as the keys are still referenced by some 
+    WeakIdentityDictionaries behave like IdentityDictionaries,
+    as long as the keys are still referenced by some
     other (non-weak) object.
     However, once the last non-weak reference ceases to exist,
     the object will be automatically removed from the Weakcollection
@@ -72,20 +72,20 @@
 !WeakIdentityDictionary methodsFor:'adding & removing'!
 
 at:key ifAbsent:exceptionBlock
-    "redefined to block interrupts 
+    "redefined to block interrupts
      (avoid change of the dictionary while accessing)"
 
     |val|
 
     (OperatingSystem blockInterrupts) ifTrue:[
-        "/ already blocked
-        ^ super at:key ifAbsent:exceptionBlock.
+	"/ already blocked
+	^ super at:key ifAbsent:exceptionBlock.
     ].
 
     [
-        val := super at:key ifAbsent:exceptionBlock.
+	val := super at:key ifAbsent:exceptionBlock.
     ] ensure:[
-        OperatingSystem unblockInterrupts.
+	OperatingSystem unblockInterrupts.
     ].
     ^ val
 
@@ -102,14 +102,14 @@
     |val|
 
     (OperatingSystem blockInterrupts) ifTrue:[
-        "/ already blocked
-        ^ super at:key put:anObject.
+	"/ already blocked
+	^ super at:key put:anObject.
     ].
 
     [
-        val := super at:key put:anObject.
+	val := super at:key put:anObject.
     ] ensure:[
-        OperatingSystem unblockInterrupts.
+	OperatingSystem unblockInterrupts.
     ].
     ^ val
 
@@ -120,24 +120,24 @@
 removeKey:aKey ifAbsent:aBlock
     "remove the association under aKey from the collection,
      return the value previously stored there.
-     If it was not in the collection return the result 
+     If it was not in the collection return the result
      from evaluating aBlock.
 
     Redefined to avoid synchronization problems, in case
-    of interrupts (otherwise, there could be some other operation 
+    of interrupts (otherwise, there could be some other operation
     on the receiver done by another process, which garbles my contents)."
 
     |ret|
 
     (OperatingSystem blockInterrupts) ifTrue:[
-        "/ already blocked
-        ^ super removeKey:aKey ifAbsent:aBlock.
+	"/ already blocked
+	^ super removeKey:aKey ifAbsent:aBlock.
     ].
 
     [
-        ret := super removeKey:aKey ifAbsent:aBlock
+	ret := super removeKey:aKey ifAbsent:aBlock
     ] ensure:[
-        OperatingSystem unblockInterrupts
+	OperatingSystem unblockInterrupts
     ].
     ^ ret
 
@@ -146,20 +146,20 @@
 !
 
 safeRemoveKey:key
-    "redefined to block interrupts 
+    "redefined to block interrupts
      (avoid change of the dictionary while accessing)"
 
     |val|
 
     (OperatingSystem blockInterrupts) ifTrue:[
-        "/ already blocked
-        ^ super safeRemoveKey:key.
+	"/ already blocked
+	^ super safeRemoveKey:key.
     ].
 
     [
-        val := super safeRemoveKey:key.
+	val := super safeRemoveKey:key.
     ] ensure:[
-        OperatingSystem unblockInterrupts.
+	OperatingSystem unblockInterrupts.
     ].
     ^ val
 
@@ -175,19 +175,19 @@
 
     "
      have to block here - dispose may be done at a low priority
-     from the background finalizer. If new items are added by a 
+     from the background finalizer. If new items are added by a
      higher prio process, the dictionary might get corrupted otherwise
     "
     wasBlocked := OperatingSystem blockInterrupts.
     [
-        keyArray 
-            forAllDeadIndicesDo:[:idx | 
-                                    valueArray basicAt:idx put:nil.
-                                    tally := tally - 1.
-                                ]
-            replacingCorpsesWith:DeletedEntry.
+	keyArray
+	    forAllDeadIndicesDo:[:idx |
+				    valueArray basicAt:idx put:nil.
+				    tally := tally - 1.
+				]
+	    replacingCorpsesWith:DeletedEntry.
     ] ensure:[
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ].
 
     "Modified: / 13.12.2001 / 14:18:17 / martin"
@@ -198,7 +198,7 @@
      disposed keys."
 
     something == #ElementExpired ifTrue:[
-        self clearDeadSlots.
+	self clearDeadSlots.
     ]
 
     "Created: / 7.1.1997 / 16:59:30 / stefan"
@@ -208,25 +208,25 @@
 !WeakIdentityDictionary methodsFor:'private'!
 
 findKeyOrNil:key
-    "Look for the key in the receiver.  
+    "Look for the key in the receiver.
      If it is found, return the index,
-     otherwise the index of the first unused slot. 
+     otherwise the index of the first unused slot.
      Grow the receiver, if key was not found, and no unused slots were present.
 
      Warning: an empty slot MUST be filled by the sender - it is only to be sent
-              by at:put: / add: - like methods."
+	      by at:put: / add: - like methods."
 
     |index  "{ Class:SmallInteger }"
      length "{ Class:SmallInteger }"
-     startIndex probe 
+     startIndex probe
      delIndex "{ Class:SmallInteger }"|
 
     (OperatingSystem blockInterrupts) ifFalse:[
-        "/
-        "/ may never be entered with interrupts enabled
-        "/
-        OperatingSystem unblockInterrupts.
-        self error:'unblocked call of findKeyOrNil'.
+	"/
+	"/ may never be entered with interrupts enabled
+	"/
+	OperatingSystem unblockInterrupts.
+	self error:'unblocked call of findKeyOrNil'.
     ].
 
     delIndex := 0.
@@ -235,39 +235,39 @@
     startIndex := index := self initialIndexForKey:key.
 
     [
-        probe := keyArray basicAt:index.
-        key == probe ifTrue:[^ index].
-        probe isNil ifTrue:[
-            delIndex == 0 ifTrue:[^ index].
-            keyArray basicAt:delIndex put:nil.
-            ^ delIndex
-        ].
+	probe := keyArray basicAt:index.
+	key == probe ifTrue:[^ index].
+	probe isNil ifTrue:[
+	    delIndex == 0 ifTrue:[^ index].
+	    keyArray basicAt:delIndex put:nil.
+	    ^ delIndex
+	].
 
-        probe == 0 ifTrue:[
-            probe := DeletedEntry.
-            keyArray basicAt:index put:probe.
-            valueArray basicAt:index put:nil.
-            tally := tally - 1.
-        ].
+	probe class == SmallInteger ifTrue:[
+	    probe := DeletedEntry.
+	    keyArray basicAt:index put:probe.
+	    valueArray basicAt:index put:nil.
+	    tally := tally - 1.
+	].
 
-        delIndex == 0 ifTrue:[
-            probe == DeletedEntry ifTrue:[
-                delIndex := index
-            ]
-        ].
+	delIndex == 0 ifTrue:[
+	    probe == DeletedEntry ifTrue:[
+		delIndex := index
+	    ]
+	].
 
-        index == length ifTrue:[
-            index := 1
-        ] ifFalse:[
-            index := index + 1
-        ].
-        index == startIndex ifTrue:[
-            delIndex ~~ 0 ifTrue:[
-                keyArray basicAt:delIndex put:nil.
-                ^ delIndex
-            ].
-            ^ self grow findKeyOrNil:key
-        ].
+	index == length ifTrue:[
+	    index := 1
+	] ifFalse:[
+	    index := index + 1
+	].
+	index == startIndex ifTrue:[
+	    delIndex ~~ 0 ifTrue:[
+		keyArray basicAt:delIndex put:nil.
+		^ delIndex
+	    ].
+	    ^ self grow findKeyOrNil:key
+	].
     ] loop.
 
     "Modified: 30.1.1997 / 15:04:34 / cg"
@@ -282,14 +282,14 @@
 "/ 'grow:' printCR.
 
     (OperatingSystem blockInterrupts) ifTrue:[
-        "/ already blocked
-        ^ super grow:newSize.
+	"/ already blocked
+	^ super grow:newSize.
     ].
 
     [
-        super grow:newSize
+	super grow:newSize
     ] ensure:[
-        OperatingSystem unblockInterrupts
+	OperatingSystem unblockInterrupts
     ].
 
     "Created: 28.1.1997 / 23:41:39 / cg"
@@ -304,15 +304,15 @@
 "/ 'setTally:' printCR.
 
     (OperatingSystem blockInterrupts) ifTrue:[
-        "/ already blocked
-        super initializeForCapacity:minSize.
-        ^ self.
+	"/ already blocked
+	super initializeForCapacity:minSize.
+	^ self.
     ].
 
     [
-        super initializeForCapacity:minSize
+	super initializeForCapacity:minSize
     ] ensure:[
-        OperatingSystem unblockInterrupts
+	OperatingSystem unblockInterrupts
     ].
 
     "Created: 29.1.1997 / 11:40:12 / cg"
@@ -341,15 +341,15 @@
 "/ 'rehash' printCR.
 
     (OperatingSystem blockInterrupts) ifTrue:[
-        "/ already blocked
-        super rehash.
-        ^ self.
+	"/ already blocked
+	super rehash.
+	^ self.
     ].
 
     [
-        super rehash
+	super rehash
     ] ensure:[
-        OperatingSystem unblockInterrupts
+	OperatingSystem unblockInterrupts
     ].
 
     "Created: 29.1.1997 / 11:39:42 / cg"
@@ -359,20 +359,20 @@
 !WeakIdentityDictionary methodsFor:'testing'!
 
 includes:anObject
-    "redefined to block interrupts 
+    "redefined to block interrupts
      (avoid change of the dictionary while accessing)"
 
     |val|
 
     (OperatingSystem blockInterrupts) ifTrue:[
-        "/ already blocked
-        ^ super includes:anObject.
+	"/ already blocked
+	^ super includes:anObject.
     ].
 
     [
-        val := super includes:anObject.
+	val := super includes:anObject.
     ] ensure:[
-        OperatingSystem unblockInterrupts.
+	OperatingSystem unblockInterrupts.
     ].
     ^ val
 
@@ -382,20 +382,20 @@
 !
 
 includesKey:key
-    "redefined to block interrupts 
+    "redefined to block interrupts
      (avoid change of the dictionary while accessing)"
 
     |val|
 
     (OperatingSystem blockInterrupts) ifTrue:[
-        "/ already blocked
-        ^ super includesKey:key.
+	"/ already blocked
+	^ super includesKey:key.
     ].
 
     [
-        val := super includesKey:key.
+	val := super includesKey:key.
     ] ensure:[
-        OperatingSystem unblockInterrupts.
+	OperatingSystem unblockInterrupts.
     ].
     ^ val
 
@@ -413,6 +413,6 @@
 !WeakIdentityDictionary class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/WeakIdentityDictionary.st,v 1.46 2015-05-09 11:58:44 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/WeakIdentitySet.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/WeakIdentitySet.st	Fri Jul 24 08:06:37 2015 +0100
@@ -47,17 +47,17 @@
     if you forget to #release it).
 
     [Warning:]
-        If you use this, be very careful since the collections size changes
-        'magically' - for example, testing for being nonEmpty and then
-        removing the first element may fail, since the element may vanish inbetween.
-        In general, never trust the value as returned by the size/isEmpty messages.
-        WeakIdentitySet is not meant as a 'public' class.
+	If you use this, be very careful since the collections size changes
+	'magically' - for example, testing for being nonEmpty and then
+	removing the first element may fail, since the element may vanish inbetween.
+	In general, never trust the value as returned by the size/isEmpty messages.
+	WeakIdentitySet is not meant as a 'public' class.
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [See also:]
-        WeakArray WeakIdentityDictionary
+	WeakArray WeakIdentityDictionary
 "
 ! !
 
@@ -76,13 +76,13 @@
 goodSizeFrom:arg
     "return a good array size for the given argument.
      Since WeakIdentitySets are mostly used for dependency management, we typically
-     have only a small number of elements in the set. 
+     have only a small number of elements in the set.
      Therefore use exact size for small sets
      (instead of rounding up to the next prime 11)."
 
     arg <= 10 ifTrue:[
-        arg < 1 ifTrue:[^ 1].
-        ^ arg.
+	arg < 1 ifTrue:[^ 1].
+	^ arg.
     ].
     ^ super goodSizeFrom:arg
 ! !
@@ -99,20 +99,20 @@
      element|
 
     index := 1.
-    "/ allow for the size to change during enumeration 
+    "/ allow for the size to change during enumeration
     [index <= keyArray size] whileTrue:[
-        element := keyArray basicAt:index.
-        element notNil ifTrue:[
-            element ~~ 0 ifTrue:[
-                element ~~ DeletedEntry ifTrue:[
-                    element == NilEntry ifTrue:[
-                        element := nil.
-                    ].
-                    ^ element
-                ]
-            ]
-        ].
-        index := index + 1
+	element := keyArray basicAt:index.
+	element notNil ifTrue:[
+	    element class ~~ SmallInteger ifTrue:[
+		element ~~ DeletedEntry ifTrue:[
+		    element == NilEntry ifTrue:[
+			element := nil.
+		    ].
+		    ^ element
+		]
+	    ]
+	].
+	index := index + 1
     ].
 
     ^ exceptionValue value.
@@ -120,25 +120,25 @@
 
 !WeakIdentitySet methodsFor:'adding & removing'!
 
-add:newElement 
-    "add the argument, newElement to the receiver. 
+add:newElement
+    "add the argument, newElement to the receiver.
      Returns the argument, newElement (sigh).
 
-     Redefined to avoid synchronization problems, in case of interrupts 
+     Redefined to avoid synchronization problems, in case of interrupts
      (otherwise, there could be some other operation on the receiver
        done by another process, which garbles my contents)"
 
     |ret|
 
     (OperatingSystem blockInterrupts) ifTrue:[
-        "/ already blocked
-        ^ super add:newElement.
+	"/ already blocked
+	^ super add:newElement.
     ].
 
     [
-        ret := super add:newElement.
+	ret := super add:newElement.
     ] ensure:[
-        OperatingSystem unblockInterrupts
+	OperatingSystem unblockInterrupts
     ].
     ^ ret
 
@@ -146,21 +146,21 @@
 !
 
 remove:anObject ifAbsent:exceptionBlock
-    "redefined to avoid synchronization problems, in case of interrupts 
+    "redefined to avoid synchronization problems, in case of interrupts
      (otherwise, there could be some other operation on the receiver
        done by another process, which garbles my contents)"
 
     |ret|
 
     (OperatingSystem blockInterrupts) ifTrue:[
-        "/ already blocked
-        ^ super remove:anObject ifAbsent:exceptionBlock.
+	"/ already blocked
+	^ super remove:anObject ifAbsent:exceptionBlock.
     ].
 
     [
-        ret := super remove:anObject ifAbsent:exceptionBlock
+	ret := super remove:anObject ifAbsent:exceptionBlock
     ] ensure:[
-        OperatingSystem unblockInterrupts
+	OperatingSystem unblockInterrupts
     ].
     ^ ret
 
@@ -175,15 +175,15 @@
     |wasBlocked|
 
     something == #ElementExpired ifTrue:[
-        "
-         must block interrupts here - finalization
-         may be done at low prio in the background
-         finalizer, we do not want to be interrupted
-         while rehashing
-        "
-        wasBlocked := OperatingSystem blockInterrupts.
-        keyArray forAllDeadIndicesDo:[:idx | tally := tally - 1] replacingCorpsesWith:DeletedEntry.
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	"
+	 must block interrupts here - finalization
+	 may be done at low prio in the background
+	 finalizer, we do not want to be interrupted
+	 while rehashing
+	"
+	wasBlocked := OperatingSystem blockInterrupts.
+	keyArray forAllDeadIndicesDo:[:idx | tally := tally - 1] replacingCorpsesWith:DeletedEntry.
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ].
 
     "Created: 7.1.1997 / 17:00:33 / stefan"
@@ -202,42 +202,42 @@
      element|
 
     index := 1.
-    "/ allow for the size to change during enumeration 
+    "/ allow for the size to change during enumeration
     [index <= keyArray size] whileTrue:[
-        element := keyArray basicAt:index.
-        element notNil ifTrue:[
-            element ~~ 0 ifTrue:[
-                element ~~ DeletedEntry ifTrue:[
-                    aBlock value:element
-                ]
-            ]
-        ].
-        index := index + 1
+	element := keyArray basicAt:index.
+	element notNil ifTrue:[
+	    element class ~~ SmallInteger ifTrue:[
+		element ~~ DeletedEntry ifTrue:[
+		    aBlock value:element
+		]
+	    ]
+	].
+	index := index + 1
     ]
 ! !
 
 !WeakIdentitySet methodsFor:'private'!
 
 findKeyOrNil:key
-    "Look for the key in the receiver.  
+    "Look for the key in the receiver.
      If it is found, return return the index, otherwise
-     the index of the first unused slot. 
+     the index of the first unused slot.
      Grow the receiver, if key was not found, and no unused slots were present.
 
      Warning: an empty slot MUST be filled by the sender - it is only to be sent
-              by at:put: / add: - like methods."
+	      by at:put: / add: - like methods."
 
     |index  "{ Class:SmallInteger }"
      length "{ Class:SmallInteger }"
-     startIndex probe 
+     startIndex probe
      delIndex "{ Class:SmallInteger }"|
 
     (OperatingSystem blockInterrupts) ifFalse:[
-        "/
-        "/ may never be entered with interrupts enabled
-        "/
-        OperatingSystem unblockInterrupts.
-        self error:'unblocked call of findKeyOrNil'.
+	"/
+	"/ may never be entered with interrupts enabled
+	"/
+	OperatingSystem unblockInterrupts.
+	self error:'unblocked call of findKeyOrNil'.
     ].
 
     delIndex := 0.
@@ -246,37 +246,37 @@
     startIndex := index := self initialIndexForKey:key.
 
     [
-        probe := keyArray basicAt:index.
-        key == probe ifTrue:[^ index].
-        probe isNil ifTrue:[
-            delIndex == 0 ifTrue:[^ index].
-            keyArray basicAt:delIndex put:nil.
-            ^ delIndex
-        ].
+	probe := keyArray basicAt:index.
+	key == probe ifTrue:[^ index].
+	probe isNil ifTrue:[
+	    delIndex == 0 ifTrue:[^ index].
+	    keyArray basicAt:delIndex put:nil.
+	    ^ delIndex
+	].
 
-        probe == 0 ifTrue:[
-            probe := DeletedEntry.
-            keyArray basicAt:index put:probe.
-            tally := tally - 1.
-        ].
-        delIndex == 0 ifTrue:[
-            probe == DeletedEntry ifTrue:[
-                delIndex := index
-            ]
-        ].
+	probe class == SmallInteger ifTrue:[
+	    probe := DeletedEntry.
+	    keyArray basicAt:index put:probe.
+	    tally := tally - 1.
+	].
+	delIndex == 0 ifTrue:[
+	    probe == DeletedEntry ifTrue:[
+		delIndex := index
+	    ]
+	].
 
-        index == length ifTrue:[
-            index := 1
-        ] ifFalse:[
-            index := index + 1
-        ].
-        index == startIndex ifTrue:[
-            delIndex ~~ 0 ifTrue:[
-                keyArray basicAt:delIndex put:nil.
-                ^ delIndex
-            ].
-            ^ self grow findKeyOrNil:key
-        ].
+	index == length ifTrue:[
+	    index := 1
+	] ifFalse:[
+	    index := index + 1
+	].
+	index == startIndex ifTrue:[
+	    delIndex ~~ 0 ifTrue:[
+		keyArray basicAt:delIndex put:nil.
+		^ delIndex
+	    ].
+	    ^ self grow findKeyOrNil:key
+	].
     ] loop.
 
     "Modified: 30.1.1997 / 15:04:38 / cg"
@@ -304,6 +304,6 @@
 !WeakIdentitySet class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/WeakIdentitySet.st,v 1.42 2014-06-23 09:00:21 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/WeakValueDictionary.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/WeakValueDictionary.st	Fri Jul 24 08:06:37 2015 +0100
@@ -38,8 +38,8 @@
 
 documentation
 "
-    WeakValueDictionaries behave like Dictionaries, 
-    as long as the values are still referenced by some 
+    WeakValueDictionaries behave like Dictionaries,
+    as long as the values are still referenced by some
     other (non-weak) object.
     However, once the last non-weak reference ceases to exist,
     the Dictionary will return nil for the value at position key.
@@ -52,10 +52,10 @@
       In general, never trust the value as returned by the size/isEmpty messages.
 
     [author:]
-        Stefan Vogel
+	Stefan Vogel
 
     [See also:]
-        WeakArray WeakIdentityDictionary WeakIdentitySet
+	WeakArray WeakIdentityDictionary WeakIdentitySet
 "
 ! !
 
@@ -70,10 +70,10 @@
     |ret|
 
     [
-        ret := super at:key ifAbsent:[^ somethingRespondingToValue value].
-        ret = 0 ifTrue:[
-            ret := somethingRespondingToValue value
-        ].
+	ret := super at:key ifAbsent:[^ somethingRespondingToValue value].
+	ret class == SmallInteger ifTrue:[
+	    ret := somethingRespondingToValue value
+	].
     ] valueUninterruptably.
     ^ ret
 !
@@ -86,12 +86,12 @@
      Redefined to block interrupts, to avoid trouble when dependencies
      are added within interrupting high prio processes.
      WARNING: do not add elements while iterating over the receiver.
-              Iterate over a copy to do this."
+	      Iterate over a copy to do this."
 
     |ret|
 
     [
-        ret := super at:key ifAbsentPut:anObject.
+	ret := super at:key ifAbsentPut:anObject.
     ] valueUninterruptably.
     ^ ret
 !
@@ -105,7 +105,7 @@
     |ret|
 
     [
-        ret := super at:key put:anObject.
+	ret := super at:key put:anObject.
     ] valueUninterruptably.
     ^ ret
 
@@ -117,17 +117,17 @@
 removeKey:aKey ifAbsent:aBlock
     "remove the association under aKey from the collection,
      return the value previously stored there.
-     If it was not in the collection return the result 
+     If it was not in the collection return the result
      from evaluating aBlock.
 
     Redefined to avoid synchronization problems, in case
-    of interrupts (otherwise, there could be some other operation 
+    of interrupts (otherwise, there could be some other operation
     on the receiver done by another process, which garbles my contents)."
 
     |ret|
 
     [
-        ret := super removeKey:aKey ifAbsent:aBlock
+	ret := super removeKey:aKey ifAbsent:aBlock
     ] valueUninterruptably.
     ^ ret
 
@@ -138,17 +138,17 @@
 removeValue:aKey ifAbsent:aBlock
     "remove the association under aValue from the collection,
      return the key previously stored there.
-     If it was not in the collection return the result 
+     If it was not in the collection return the result
      from evaluating aBlock.
 
     Redefined to avoid synchronization problems, in case
-    of interrupts (otherwise, there could be some other operation 
+    of interrupts (otherwise, there could be some other operation
     on the receiver done by another process, which garbles my contents)."
 
     |ret|
 
     [
-        ret := super removeValue:aKey ifAbsent:aBlock
+	ret := super removeValue:aKey ifAbsent:aBlock
     ] valueUninterruptably.
     ^ ret.
 
@@ -165,7 +165,7 @@
     |wasBlocked|
 
     something == #ElementExpired ifTrue:[
-        self clearDeadSlots.
+	self clearDeadSlots.
     ]
 
     "Created: 7.1.1997 / 16:59:30 / stefan"
@@ -178,19 +178,19 @@
 
     "
      have to block here - dispose may be done at a low priority
-     from the background finalizer. If new items are added by a 
+     from the background finalizer. If new items are added by a
      higher prio process, the dictionary might get corrupted otherwise
     "
     wasBlocked := OperatingSystem blockInterrupts.
 
-    valueArray 
-        forAllDeadIndicesDo:[:idx | keyArray at:idx put:DeletedEntry.
-                                    tally := tally - 1.
-                            ]
-        replacingCorpsesWith:nil.
+    valueArray
+	forAllDeadIndicesDo:[:idx | keyArray at:idx put:DeletedEntry.
+				    tally := tally - 1.
+			    ]
+	replacingCorpsesWith:nil.
 
     wasBlocked ifFalse:[
-        OperatingSystem unblockInterrupts.
+	OperatingSystem unblockInterrupts.
     ].
 
     "Modified: / 13.12.2001 / 14:18:56 / martin"
@@ -225,13 +225,13 @@
 !WeakValueDictionary methodsFor:'testing'!
 
 includes:anObject
-    "redefined to block interrupts 
+    "redefined to block interrupts
      (avoid change of the dictionary while accessing)"
 
     |val|
 
     [
-        val := super includes:anObject.
+	val := super includes:anObject.
     ] valueUninterruptably.
     ^ val
 
@@ -241,13 +241,13 @@
 !
 
 includesKey:key
-    "redefined to block interrupts 
+    "redefined to block interrupts
      (avoid change of the dictionary while accessing)"
 
     |val|
 
     [
-        val := super includesKey:key.
+	val := super includesKey:key.
     ] valueUninterruptably.
     ^ val
 
@@ -265,6 +265,6 @@
 !WeakValueDictionary class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/WeakValueDictionary.st,v 1.20 2014-12-30 12:35:34 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/Win32OperatingSystem.st	Wed Jul 22 06:38:29 2015 +0200
+++ b/Win32OperatingSystem.st	Fri Jul 24 08:06:37 2015 +0100
@@ -10616,15 +10616,14 @@
 					LPTIME_ZONE_INFORMATION, // - should be, but is not defined: PDYNAMIC_TIME_ZONE_INFORMATION,
 					LPTIME_ZONE_INFORMATION);
 	    static P_GetTimeZoneInformationForYear pGetTimeZoneInformationForYear;
-
-	    if (pGetTimeZoneInformationForYear == NULL) {
+	    static int haveTriedToGet_P_GetTimeZoneInformationForYear = 0;
+
+	    if (! haveTriedToGet_P_GetTimeZoneInformationForYear) {
 		pGetTimeZoneInformationForYear =
 		    (P_GetTimeZoneInformationForYear)GetProcAddress(GetModuleHandle("kernel32.dll"), "GetTimeZoneInformationForYear");
-		if (pGetTimeZoneInformationForYear == NULL) {
-		    pGetTimeZoneInformationForYear = false;
-		}
-	    }
-	    if (pGetTimeZoneInformationForYear == false) {
+		haveTriedToGet_P_GetTimeZoneInformationForYear = 1;
+	    }
+	    if (pGetTimeZoneInformationForYear == NULL) {
 		error = __mkSmallInteger(@symbol(primitiveFailed));
 		goto out;
 	    } else {
@@ -10810,17 +10809,17 @@
 					LPTIME_ZONE_INFORMATION, // - should be, but is not defined: PDYNAMIC_TIME_ZONE_INFORMATION,
 					LPTIME_ZONE_INFORMATION);
 	    static P_GetTimeZoneInformationForYear pGetTimeZoneInformationForYear;
-
-	    if (pGetTimeZoneInformationForYear == NULL) {
+	    static int haveTriedToGet_P_GetTimeZoneInformationForYear = 0;
+
+	    if (! haveTriedToGet_P_GetTimeZoneInformationForYear) {
 		pGetTimeZoneInformationForYear =
 		    (P_GetTimeZoneInformationForYear)GetProcAddress(GetModuleHandle("kernel32.dll"), "GetTimeZoneInformationForYear");
-		if (pGetTimeZoneInformationForYear == NULL) {
-		    // ignore this error and fall back to GetTimeZoneInformation()
-		    reason = @symbol(NoGetTimeZoneInformationForYear);
-		    pGetTimeZoneInformationForYear = false;
-		}
-	    }
-	    if (pGetTimeZoneInformationForYear != false) {
+		haveTriedToGet_P_GetTimeZoneInformationForYear = 1;
+	    }
+	    if (pGetTimeZoneInformationForYear == NULL) {
+		// ignore this error and fall back to GetTimeZoneInformation()
+		reason = @symbol(NoGetTimeZoneInformationForYear);
+	    } else {
 		if (pGetTimeZoneInformationForYear(localSysTime.wYear, NULL, &tzInfo)) {
 		    _stdUtcOffset = (tzInfo.Bias + tzInfo.StandardBias) * 60;
 		    isDst = (_stdUtcOffset != _utcOffset) ? true : false;