Merged with /trunk jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 04 May 2010 12:50:05 +0100
branchjv
changeset 17763 019bb9c842c5
parent 17762 6eb4414e6a31
child 17764 ff2278767be8
Merged with /trunk
Behavior.st
Block.st
ByteArray.st
CharacterArray.st
Class.st
ClassBuilder.st
ClassDescription.st
DirectoryStream.st
ExecutableFunction.st
ExternalAddress.st
ExternalBytes.st
ExternalStream.st
Filename.st
Integer.st
LargeInteger.st
Make.proto
Make.spec
Method.st
OSProcess.st
ProjectDefinition.st
SHA1Stream.st
SequenceableCollection.st
SmallInteger.st
Smalltalk.st
SystemChangeNotifier.st
UnixOperatingSystem.st
UserPreferences.st
Win32OperatingSystem.st
abbrev.stc
bc.mak
libInit.cc
libbasic.rc
stx_libbasic.st
--- a/Behavior.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/Behavior.st	Tue May 04 12:50:05 2010 +0100
@@ -93,16 +93,16 @@
 virtualMachineRelationship
 "
     Expert info follows:
-
+    --------------------
     NOTICE:
-	the stuff described below may not be available on other
-	Smalltalk implementations; be aware that these error mechanisms
-	are ST/X specials and applications using these (tricks) may
-	not be portable to other systems.
+        the stuff described below may not be available on other
+        Smalltalk implementations; be aware that these error mechanisms
+        are ST/X specials and applications using these (tricks) may
+        not be portable to other systems.
 
     WARNING:
-	do not try the examples below on (some) other smalltalk systems;
-	it has been reported, that some crash badly when doing this .... ;-)
+        do not try the examples below on (some) other smalltalk systems;
+        it has been reported, that some crash badly when doing this .... ;-)
 
     Instances of Behavior and subclasses (i.e. in sloppy words: classes)
     play a special role w.r.t. the VM. Only objects whose class-slot is marked
@@ -113,14 +113,14 @@
 
 
     Why is this so:
-
+    ---------------
     the above lets every object play the role of a class,
     which has been flagged as behaviorLike in its class's flag.
     Thus, you can create arbitrary new classLike objects and have the VM
     play with them.
     This may offer the flexibility to create a totally different object scheme
     on top of ST/X (for example: Self like objects) where any object can play
-    a classRole for another object.
+    a classRole for another object or even for itself.
 
     [A concrete application of this is found in the Structure class,
      which creates objects which are their own class !!
@@ -132,9 +132,9 @@
     object, the VM EXPECTS the object selector and methodDictionaries to be found
     at the instance positions as defined here.
     (i.e. instanceVariables with contents and semantic corresponding to
-	superclass
-	flags
-	methodDictionary
+        superclass
+        flags
+        methodDictionary
      must be present and have the same instVar-index as here).
 
     The VM (and the system) may crash badly, if this is not the case.
@@ -149,7 +149,7 @@
 
 
     Vice versa, defining 'dumb classes', which have the behaviorLike bit turned
-    of may be useful as well; if a message is sent to an instance of such
+    off may be useful as well; if a message is sent to an instance of such
     a thingy, the VM performs a recovery sequence, which is much like the
     #doesNotUnderstand: mechanism - however, since the instance is no good
     receiver of such a message, a #cannotSendMessage:to: is now sent to the
@@ -167,111 +167,132 @@
 
 
     Examples (only of theoretical interest):
-	take away the behaviorLike-flag from a class.
-	-> The instances will not understand any messages, since the VM will
-	   not recognize its class as being a class ...
-
-	|newMeta notRecognizedAsClass someInstance|
-
-	newMeta := Metaclass new.
-	newMeta flags:0.
-
-	notRecognizedAsClass := newMeta new.
-
-	someInstance := notRecognizedAsClass new.
-	someInstance perform:#isNil
+    ----------------------------------------
+        take away the behaviorLike-flag from a class.
+        -> The instances will not understand any messages, since the VM will
+           not recognize its class as being a class ...
+
+        |newMeta notRecognizedAsClass someInstance|
+
+        newMeta := Metaclass new.
+        newMeta flags:0.
+
+        notRecognizedAsClass := newMeta new.
+
+        someInstance := notRecognizedAsClass new.
+        someInstance perform:#isNil
 
 
     Of course, this is an exception which can be handled ...:
     Example:
 
-	|newMeta notRecognizedAsClass someInstance|
-
-	newMeta := Metaclass new.
-	newMeta flags:0.
-
-	notRecognizedAsClass := newMeta new.
-
-	someInstance := notRecognizedAsClass new.
-	Object errorSignal handle:[:ex |
-	    ex return
-	] do:[
-	    someInstance perform:#isNil
-	]
+        |newMeta notRecognizedAsClass someInstance|
+
+        newMeta := Metaclass new.
+        newMeta flags:0.
+
+        notRecognizedAsClass := newMeta new.
+
+        someInstance := notRecognizedAsClass new.
+        Object errorSignal handle:[:ex |
+            ex return
+        ] do:[
+            someInstance perform:#isNil
+        ]
 
 
     likewise, a doesNotUnderstand-notUnderstood can be handled:
     Example:
 
-	|newMeta funnyClass someInstance|
-
-	newMeta := Metaclass new.
-
-	funnyClass := newMeta new.
-	funnyClass setSuperclass:nil.
-
-	someInstance := funnyClass new.
-	Object errorSignal handle:[:ex |
-	     ex return
-	] do:[
-	    someInstance perform:#isNil
-	]
+        |newMeta funnyClass someInstance|
+
+        newMeta := Metaclass new.
+
+        funnyClass := newMeta new.
+        funnyClass setSuperclass:nil.
+
+        someInstance := funnyClass new.
+        Object errorSignal handle:[:ex |
+             ex return
+        ] do:[
+            someInstance perform:#isNil
+        ]
 
 
     more examples, which try to trick the VM ;-):
-	badly playing around with a classes internals ...
-
-	|newClass someInstance|
-
-	newClass := Class new.
-	newClass setSuperclass:nil.
-	someInstance := newClass new.
-	someInstance inspect
-
-
-	|newClass someInstance|
-
-	newClass := Class new.
-	newClass setSuperclass:newClass.
-	someInstance := newClass new.
-	someInstance inspect
-
-
-	|newClass someInstance|
-
-	newClass := Class new.
-	newClass setSuperclass:1.
-	someInstance := newClass new.
-	someInstance inspect
+        badly playing around with a classes internals ...
+
+        |newClass someInstance|
+
+        newClass := Class new.
+        newClass setSuperclass:nil.
+        someInstance := newClass new.
+        someInstance inspect
+
+
+        |newClass someInstance|
+
+        newClass := Class new.
+        newClass setSuperclass:newClass.
+        someInstance := newClass new.
+        someInstance inspect
+
+
+        |newClass someInstance|
+
+        newClass := Class new.
+        newClass setSuperclass:1.
+        someInstance := newClass new.
+        someInstance inspect
+
+
+    Example:
+        creating totally anonymous classes:
+
+        |newClass someInstance|
+
+        newClass := Class new.
+        someInstance := newClass new.
+        someInstance inspect
 
 
     Example:
-	creating totally anonymous classes:
-
-	|newClass someInstance|
-
-	newClass := Class new.
-	someInstance := newClass new.
-	someInstance inspect
-
-
-    Example:
-	creating totally anonymous metaclasses:
-
-	|newMeta newClass someInstance|
-
-	newMeta := Metaclass new.
-	newClass := newMeta new.
-	someInstance := newClass new.
-	someInstance inspect
+        creating totally anonymous metaclasses:
+
+        |newMeta newClass someInstance|
+
+        newMeta := Metaclass new.
+        newClass := newMeta new.
+        someInstance := newClass new.
+        someInstance inspect
 
 
     PS: if you experiment with new behaviorLike objects, you may want
-	to turn off the VM's debugPrintouts
-	with:
-		'Smalltalk debugPrinting:false'
-	and:
-		'Smalltalk infoPrinting:false'
+        to turn off the VM's debugPrintouts
+        with:
+                'Smalltalk debugPrinting:false'
+        and:
+                'Smalltalk infoPrinting:false'
+
+    Meta-Object-Protocol support:
+    -----------------------------
+    the above tricks do not affect the inline caches, and are therefore somewhat slow.
+    Another hook is the lookupObject which, if non-nil, is consulted to do the lookup
+    instead of the hardwired VM lookup algorithm, and provide a method as return value.
+    This method (if non-nil) will be put into the inline-and polymorph caches for speedy
+    call the next time. If non-nil, the lookup object is sent the:
+            lookupMethodForSelector:aSelector 
+            directedTo:searchClass 
+            for:aReceiver 
+            withArguments:argArrayOrNil 
+            from:sendingContext
+    message.
+    'searchClass' is the object class or any of its superclasses (for directed/super sends).
+    You can return any arbitrary method there - for example to implement multiple inheritance,
+    selector namespace tricks or multi-dispatch on argument types (double dispatch for a method).
+    Be aware, that the returned method is cached, and the lookup is not consulted again for the
+    same receiver/callsite combination. So the returned method should check if it's ok to be called
+    again (maybe, a synthetic method is generated and returned).
 "
 ! !
 
@@ -1267,10 +1288,6 @@
 !
 
 lookupObject: anObject
-    "set the lookupObject (Jan's MetaObjectProtocol support) or nil.
-     If non-nil, no lookup is performed by the VM, instead the lookupObject
-     has to provide a method object for message sends."
-
     anObject isNil ifTrue:[^self setLookupObject: anObject].
 
     (anObject respondsTo: #lookupMethodForSelector:directedTo:for:withArguments:from:)
@@ -1282,7 +1299,7 @@
     self setLookupObject: anObject.
 
     "Created: / 26-04-2010 / 13:35:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 26-04-2010 / 21:05:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 26-04-2010 / 21:05:39 / Jan Vrany <jan.vrany@fit.cvut.cz>" 
 !
 
 methodDictionary
@@ -1342,47 +1359,6 @@
     "return the receivers superclass"
 
     ^ superclass
-!
-
-superclass:aClass
-    "set the superclass - this actually creates a new class,
-     recompiling all methods for the new one. The receiving class stays
-     around anonymous to allow existing instances some life.
-     This may change in the future (adjusting existing instances)"
-
-    |owner ns name|
-
-    Class flushSubclassInfo.
-
-    "must flush caches since lookup chain changes"
-    ObjectMemory flushCaches.
-
-    "/ for correct recompilation, just create a new class ...
-    "/ but care to avoid a nameSpace change, by giving my
-    "/ full name and answering with Smalltalk to a nameSpace query.
-
-    (owner := self owningClass) notNil ifTrue:[
-	ns := owner.
-	name := self nameWithoutPrefix asSymbol
-    ] ifFalse:[
-	ns := Smalltalk.
-	name := self name
-    ].
-
-    Class classRedefinitionNotification answer:#keep do:[
-	Class nameSpaceQuerySignal answer:ns
-	do:[
-	    aClass
-		perform:(self definitionSelector)
-		withArguments:(Array with:name
-			       with:(self instanceVariableString)
-			       with:(self classVariableString)
-			       with:'' "/ pool
-			       with:(self category)).
-	]
-    ]
-
-    "Modified: / 20.6.1998 / 18:17:37 / cg"
 ! !
 
 
@@ -1839,13 +1815,21 @@
 !
 
 whichClassSatisfies: aBlock
-    |superclass|
-
-    (aBlock value: self) ifTrue: [^self].
-    superclass := self superclass.
-    ^ superclass isNil
-		ifTrue: [nil]
-		ifFalse: [superclass whichClassSatisfies: aBlock]
+    "return the first class along the superclass-chain, which satisfies aBlock.
+     Return nil, if there is none."
+
+    |cls|
+
+    cls := self.
+    [cls notNil] whileTrue:[
+        (aBlock value: cls) ifTrue: [^ cls].
+        cls := cls superclass.
+    ].
+    ^ nil
+
+    "
+     SimpleView whichClassSatisfies:[:cls | cls instanceVariableNames includes:'gc']
+    "
 !
 
 withAllSubclassesDo:aBlock
@@ -2729,6 +2713,11 @@
     ^ nil
 !
 
+flushSubclasses
+    "I dont keep my subclasses - but if anyone inherits from me,
+     it better knows how to ignore this"
+!
+
 iconInBrowserSymbol
     "can be redefined for a private icon in the browser (for me and my subclasses).
      The returned symbol must be a selector of the ToolbarIconLibrary."
@@ -3169,26 +3158,43 @@
 isSubclassOf:aClass
     "return true, if I am a subclass of the argument, aClass"
 
-    |theClass|
-
-    theClass := superclass.
-    [theClass notNil] whileTrue:[
-	(theClass == aClass) ifTrue:[^ true].
-%{
-	if (__isBehaviorLike(theClass)) {
-	    theClass = __ClassInstPtr(theClass)->c_superclass;
-	} else {
-	    theClass = nil;
-	}
+%{  /* NOCONTEXT */
+    OBJ __theClass = __INST(superclass);
+
+    while (__theClass != nil) {
+        if (__theClass == aClass) {
+            RETURN(true);
+        }
+        if (__isBehaviorLike(__theClass)) {
+            __theClass = __ClassInstPtr(__theClass)->c_superclass;
+        } else {
+            __theClass = nil;
+        }
+    }
+    RETURN (false);
 %}.
-"/        theClass := theClass superclass.
-    ].
-    ^ false
+
+"/    |theClass|
+"/
+"/    theClass := superclass.
+"/    [theClass notNil] whileTrue:[
+"/        (theClass == aClass) ifTrue:[^ true].
+"/%{
+"/        if (__isBehaviorLike(theClass)) {
+"/            theClass = __ClassInstPtr(theClass)->c_superclass;
+"/        } else {
+"/            theClass = nil;
+"/        }
+"/%}.
+"/"/        theClass := theClass superclass.
+"/    ].
+"/    ^ false
 
     "
-     String isSubclassOf:Collection
-     LinkedList isSubclassOf:Array
+     String isSubclassOf:Collection 
+     LinkedList isSubclassOf:Array  
      1 isSubclassOf:Number              <- will fail since 1 is no class
+     Number isSubclassOf:1              
     "
 !
 
@@ -4550,15 +4556,20 @@
     "Modified: 3.6.1996 / 16:03:33 / stefan"
 !
 
-whichClassDefinesClassVar: aString
-	^self whichClassSatisfies:
-			[:aClass |
-			(aClass classVarNames collect: [:each | each asString])
-				includes: aString asString]
+whichClassDefinesClassVar:aStringOrText
+    |name|
+
+    name := aStringOrText asString string.
+    ^ self whichClassSatisfies:[:aClass | aClass classVarNames includes:name]
+
+    "
+     TextView whichClassDefinesClassVar:'CachedScales' 
+     TextView whichClassDefinesClassVar:'xxx' 
+    "
 !
 
 whichClassDefinesInstVar: aString
-	^self whichClassSatisfies: [:aClass | aClass instVarNames includes: aString]
+    ^ self whichClassSatisfies: [:aClass | aClass instVarNames includes: aString]
 !
 
 whichSelectorsAssign: instVarName
@@ -4680,13 +4691,14 @@
 !Behavior class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Behavior.st 10518 2010-04-29 15:55:35Z vranyj1 $'
+    ^ '$Id: Behavior.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ 'Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.300 2010/04/07 14:52:07 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.304 2010/04/12 16:30:42 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Behavior.st 10518 2010-04-29 15:55:35Z vranyj1 $'
+    ^ '$Id: Behavior.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
+
--- a/Block.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/Block.st	Tue May 04 12:50:05 2010 +0100
@@ -548,6 +548,7 @@
     "Created: 15.11.1996 / 11:38:37 / cg"
 ! !
 
+
 !Block methodsFor:'accessing'!
 
 home
@@ -2002,12 +2003,12 @@
     signal handle:[:ex |
         retVal := exceptionBlock value.
     ] do:[
-        Processor 
-            addTimedBlock:showStopper 
-            for:me 
-            afterMilliseconds:aTimeLimit.
-
         [
+            Processor 
+                addTimedBlock:showStopper 
+                for:me 
+                afterMilliseconds:aTimeLimit.
+
             retVal := self value.
         ] ensure:[ Processor removeTimedBlock:showStopper ].
     ].
@@ -2900,15 +2901,16 @@
 !Block class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Block.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: Block.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/Block.st,v 1.175 2009/12/17 11:46:36 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/Block.st,v 1.176 2010/04/23 13:33:01 mb Exp §'
 !
 
 version_SVN
-    ^ '$Id: Block.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: Block.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 Block initialize!
+
--- a/ByteArray.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/ByteArray.st	Tue May 04 12:50:05 2010 +0100
@@ -182,8 +182,8 @@
     |answer|
 
     answer := self copy.
-    1 to: self size do: [ :each | 
-        answer at: each put: ((self at: each) bitXor: (aByteArray at: each))
+    1 to: self size do: [ :each |
+	answer at: each put: ((self at: each) bitXor: (aByteArray at: each))
     ].
     ^ answer
 ! !
@@ -284,20 +284,20 @@
     REGISTER OBJ cls;
 
     if (__isSmallInteger(index)) {
-        indx = __intVal(index) - 1;
-        slf = self;
-
-        byte = indx / 8;
-        indx = indx % 8;
-
-        if ((cls = __qClass(slf)) != @global(ByteArray)) {
-            if (indx < 0) goto badIndex;
-            byte += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-        }
-        nIndex = __byteArraySize(slf);
-        if ((unsigned)byte < (unsigned)nIndex) {
-            RETURN ( __mkSmallInteger(((__ByteArrayInstPtr(slf)->ba_element[byte] & (1 << indx)) != 0)) );
-        }
+	indx = __intVal(index) - 1;
+	slf = self;
+
+	byte = indx / 8;
+	indx = indx % 8;
+
+	if ((cls = __qClass(slf)) != @global(ByteArray)) {
+	    if (indx < 0) goto badIndex;
+	    byte += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+	}
+	nIndex = __byteArraySize(slf);
+	if ((unsigned)byte < (unsigned)nIndex) {
+	    RETURN ( __mkSmallInteger(((__ByteArrayInstPtr(slf)->ba_element[byte] & (1 << indx)) != 0)) );
+	}
     }
 badIndex: ;
 %}.
@@ -307,7 +307,7 @@
     ^  byte bitTest:(1 bitShift:bitIndex0).
 
    "
-     #[ 1 1 1 1 ] bitAt:9     
+     #[ 1 1 1 1 ] bitAt:9
      #[ 1 1 1 1 ] bitAt:11
      #[ 2 2 2 2 ] bitAt:10
    "
@@ -657,38 +657,38 @@
     REGISTER int indx;
     int nIndex;
     union {
-        unsigned char u_char[2];
-        unsigned short u_ushort;
+	unsigned char u_char[2];
+	unsigned short u_ushort;
     } val;
     unsigned char *byteP;
 
     if (__isSmallInteger(index)) {
-        indx = __intVal(index);
-        if (indx > 0) {
-            if (!__isByteArrayLike(self))
-                indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
-            nIndex = __byteArraySize(self);
-            if ((indx+1) <= nIndex) {
-                byteP = (unsigned char *)(__ByteArrayInstPtr(self)->ba_element) + indx - 1;
+	indx = __intVal(index);
+	if (indx > 0) {
+	    if (!__isByteArrayLike(self))
+		indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
+	    nIndex = __byteArraySize(self);
+	    if ((indx+1) <= nIndex) {
+		byteP = (unsigned char *)(__ByteArrayInstPtr(self)->ba_element) + indx - 1;
 #if defined(__i386__) || defined(UNALIGNED_FETCH_OK)
-                val.u_ushort = ((unsigned short *)byteP)[0];
+		val.u_ushort = ((unsigned short *)byteP)[0];
 #else
-                /*
-                 * mhmh to be measured:
-                 *   the if may hurt more than the additional
-                 *   memory cycles on some machines ...
-                 */
-                if (((INT)byteP & 1) == 0) {
-                    /* aligned */
-                    val.u_ushort = ((unsigned short *)byteP)[0];
-                } else {
-                    val.u_char[0] = byteP[0];
-                    val.u_char[1] = byteP[1];
-                }
+		/*
+		 * mhmh to be measured:
+		 *   the if may hurt more than the additional
+		 *   memory cycles on some machines ...
+		 */
+		if (((INT)byteP & 1) == 0) {
+		    /* aligned */
+		    val.u_ushort = ((unsigned short *)byteP)[0];
+		} else {
+		    val.u_char[0] = byteP[0];
+		    val.u_char[1] = byteP[1];
+		}
 #endif
-                RETURN ( __mkSmallInteger((val.u_ushort)) );
-            }
-        }
+		RETURN ( __mkSmallInteger((val.u_ushort)) );
+	    }
+	}
     }
 %}.
     ^ super wordAt:index
@@ -708,59 +708,59 @@
     unsigned char *byteP;
 
     if (__isSmallInteger(index)) {
-        indx = __intVal(index);
-        if (indx > 0) {
-            if (!__isByteArrayLike(self))
-                indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
-            nIndex = __byteArraySize(self);
-            if ((indx+1) <= nIndex) {
-                byteP = (unsigned char *)(__ByteArrayInstPtr(self)->ba_element) + indx - 1;
-                if (msb == true) {
-                    /*
-                     * most significant byte first (i.e sparc order)
-                     */
+	indx = __intVal(index);
+	if (indx > 0) {
+	    if (!__isByteArrayLike(self))
+		indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
+	    nIndex = __byteArraySize(self);
+	    if ((indx+1) <= nIndex) {
+		byteP = (unsigned char *)(__ByteArrayInstPtr(self)->ba_element) + indx - 1;
+		if (msb == true) {
+		    /*
+		     * most significant byte first (i.e sparc order)
+		     */
 #if defined(__MSBFIRST__)
-                    /*
-                     * mhmh to be measured:
-                     *   the if may hurt more than the additional
-                     *   memory cycles on some machines ...
-                     */
-                    if (((INT)byteP & 1) == 0) {
-                        /* aligned */
-                        val = ((unsigned short *)byteP)[0];
-                    } else
+		    /*
+		     * mhmh to be measured:
+		     *   the if may hurt more than the additional
+		     *   memory cycles on some machines ...
+		     */
+		    if (((INT)byteP & 1) == 0) {
+			/* aligned */
+			val = ((unsigned short *)byteP)[0];
+		    } else
 #endif
-                    {
-                        val = byteP[0];
-                        val = (val << 8) + byteP[1];
-                    }
-                } else {
-                    /*
-                     * least significant byte first (i.e i386/alpha order)
-                     */
+		    {
+			val = byteP[0];
+			val = (val << 8) + byteP[1];
+		    }
+		} else {
+		    /*
+		     * least significant byte first (i.e i386/alpha order)
+		     */
 #if defined(__i386__) || (defined(__LSBFIRST__) && defined(UNALIGNED_FETCH_OK))
-                    val = ((unsigned short *)byteP)[0];
+		    val = ((unsigned short *)byteP)[0];
 #else
 # if defined(__LSBFIRST__)
-                    /*
-                     * mhmh to be measured:
-                     *   the if may hurt more than the additional
-                     *   memory cycles on some machines ...
-                     */
-                    if (((INT)byteP & 1) == 0) {
-                        /* aligned */
-                        val = ((unsigned short *)byteP)[0];
-                    } else
+		    /*
+		     * mhmh to be measured:
+		     *   the if may hurt more than the additional
+		     *   memory cycles on some machines ...
+		     */
+		    if (((INT)byteP & 1) == 0) {
+			/* aligned */
+			val = ((unsigned short *)byteP)[0];
+		    } else
 # endif
-                    {
-                        val = byteP[1];
-                        val = (val << 8) + byteP[0];
-                    }
+		    {
+			val = byteP[1];
+			val = (val << 8) + byteP[0];
+		    }
 #endif
-                }
-                RETURN ( __mkSmallInteger(val) );
-            }
-        }
+		}
+		RETURN ( __mkSmallInteger(val) );
+	    }
+	}
     }
 %}.
     ^ super wordAt:index MSB:msb
@@ -780,41 +780,41 @@
     int nIndex;
     int v;
     union {
-        unsigned char u_char[2];
-        unsigned short u_ushort;
+	unsigned char u_char[2];
+	unsigned short u_ushort;
     } val;
     unsigned char *byteP;
 
     if (__bothSmallInteger(index, value)) {
-        indx = __intVal(index);
-        if (indx > 0) {
-            if (!__isByteArrayLike(self))
-                indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
-            nIndex = __byteArraySize(self);
-            if ((indx+1) <= nIndex) {
-                val.u_ushort = v = __intVal(value);
-                if ((v & ~0xFFFF) == 0 /* i.e. (val >= 0) && (val <= 0xFFFF) */) {
-                    byteP = (unsigned char *)(__ByteArrayInstPtr(self)->ba_element) + indx - 1;
+	indx = __intVal(index);
+	if (indx > 0) {
+	    if (!__isByteArrayLike(self))
+		indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
+	    nIndex = __byteArraySize(self);
+	    if ((indx+1) <= nIndex) {
+		val.u_ushort = v = __intVal(value);
+		if ((v & ~0xFFFF) == 0 /* i.e. (val >= 0) && (val <= 0xFFFF) */) {
+		    byteP = (unsigned char *)(__ByteArrayInstPtr(self)->ba_element) + indx - 1;
 #if defined(__i386__) || defined(UNALIGNED_FETCH_OK)
-                    ((unsigned short *)byteP)[0] = val.u_ushort;
+		    ((unsigned short *)byteP)[0] = val.u_ushort;
 #else
-                    /*
-                     * mhmh to be measured:
-                     *   the if may hurt more than the additional
-                     *   memory cycles on some machines ...
-                     */
-                    if (((INT)byteP & 1) == 0) {
-                        /* aligned */
-                        ((unsigned short *)byteP)[0] = val.u_ushort;
-                    } else {
-                        byteP[0] = val.u_char[0];
-                        byteP[1] = val.u_char[1];
-                    }
+		    /*
+		     * mhmh to be measured:
+		     *   the if may hurt more than the additional
+		     *   memory cycles on some machines ...
+		     */
+		    if (((INT)byteP & 1) == 0) {
+			/* aligned */
+			((unsigned short *)byteP)[0] = val.u_ushort;
+		    } else {
+			byteP[0] = val.u_char[0];
+			byteP[1] = val.u_char[1];
+		    }
 #endif
-                    RETURN ( value );
-                }
-            }
-        }
+		    RETURN ( value );
+		}
+	    }
+	}
     }
 %}.
     ^ super wordAt:index put:value
@@ -844,62 +844,62 @@
     unsigned char *byteP;
 
     if (__bothSmallInteger(index, value)) {
-        indx = __intVal(index);
-        if (indx > 0) {
-            if (!__isByteArrayLike(self))
-                indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
-            nIndex = __byteArraySize(self);
-            if ((indx+1) <= nIndex) {
-                val = __intVal(value);
-                if ((val & ~0xFFFF) == 0 /* i.e. (val >= 0) && (val <= 0xFFFF) */) {
-                    byteP = (unsigned char *)(__ByteArrayInstPtr(self)->ba_element) + indx - 1;
-                    if (msb == true) {
-                        /*
-                         * most significant byte first (i.e sparc order)
-                         */
+	indx = __intVal(index);
+	if (indx > 0) {
+	    if (!__isByteArrayLike(self))
+		indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
+	    nIndex = __byteArraySize(self);
+	    if ((indx+1) <= nIndex) {
+		val = __intVal(value);
+		if ((val & ~0xFFFF) == 0 /* i.e. (val >= 0) && (val <= 0xFFFF) */) {
+		    byteP = (unsigned char *)(__ByteArrayInstPtr(self)->ba_element) + indx - 1;
+		    if (msb == true) {
+			/*
+			 * most significant byte first (i.e sparc order)
+			 */
 #if defined(__MSBFIRST__)
-                        /*
-                         * mhmh to be measured:
-                         *   the if may hurt more than the additional
-                         *   memory cycles on some machines ...
-                         */
-                        if (((INT)byteP & 1) == 0) {
-                            /* aligned */
-                            ((unsigned short *)byteP)[0] = val;
-                        } else
+			/*
+			 * mhmh to be measured:
+			 *   the if may hurt more than the additional
+			 *   memory cycles on some machines ...
+			 */
+			if (((INT)byteP & 1) == 0) {
+			    /* aligned */
+			    ((unsigned short *)byteP)[0] = val;
+			} else
 #endif
-                        {
-                            byteP[1] = val & 0xFF;
-                            byteP[0] = (val>>8) & 0xFF;
-                        }
-                    } else {
-                        /*
-                         * least significant byte first (i.e i386/alpha order)
-                         */
+			{
+			    byteP[1] = val & 0xFF;
+			    byteP[0] = (val>>8) & 0xFF;
+			}
+		    } else {
+			/*
+			 * least significant byte first (i.e i386/alpha order)
+			 */
 #if defined(__i386__) || (defined(__LSBFIRST__) && defined(UNALIGNED_FETCH_OK))
-                        ((unsigned short *)byteP)[0] = val;
+			((unsigned short *)byteP)[0] = val;
 #else
 # if defined(__LSBFIRST__)
-                        /*
-                         * mhmh to be measured:
-                         *   the if may hurt more than the additional
-                         *   memory cycles on some machines ...
-                         */
-                        if (((INT)byteP & 1) == 0) {
-                            /* aligned */
-                            ((unsigned short *)byteP)[0] = val;
-                        } else
+			/*
+			 * mhmh to be measured:
+			 *   the if may hurt more than the additional
+			 *   memory cycles on some machines ...
+			 */
+			if (((INT)byteP & 1) == 0) {
+			    /* aligned */
+			    ((unsigned short *)byteP)[0] = val;
+			} else
 # endif
-                        {
-                            byteP[0] = val & 0xFF;
-                            byteP[1] = (val>>8) & 0xFF;
-                        }
+			{
+			    byteP[0] = val & 0xFF;
+			    byteP[1] = (val>>8) & 0xFF;
+			}
 #endif
-                    }
-                    RETURN ( value );
-                }
-            }
-        }
+		    }
+		    RETURN ( value );
+		}
+	    }
+	}
     }
 %}.
     ^ super wordAt:index put:value MSB:msb
@@ -933,76 +933,76 @@
     INT addrDelta;
 
     if (s == self) {
-        RETURN ( true );
+	RETURN ( true );
     }
     if (! __isNonNilObject(s)) {
-        RETURN ( false );
+	RETURN ( false );
     }
 
     cls = __qClass(s);
     myCls = __qClass(self);
 
     if (cls == myCls) {
-        l2 = __byteArraySize(s);
-        l1 = __byteArraySize(self);
-        if (l1 != l2) {
-            RETURN ( false );
-        }
-
-        cp1 = __stringVal(self);
-        cp2 = __stringVal(s);
-
-        /*
-         * care for instances of subclasses ...
-         */
-        if (cls != ByteArray) {
-            int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-
-            cp2 += n;
-            cp1 += n;
-            l1 -= n;
-        }
-
-        addrDelta = cp2 - cp1;
-        while (l1 >= (sizeof(unsigned INT) * 4)) {
-            if (((unsigned INT *)cp1)[0] != ((unsigned INT *)(cp1+addrDelta))[0]) {
-                RETURN (false);
-            }
-            if (((unsigned INT *)cp1)[1] != ((unsigned INT *)(cp1+addrDelta))[1]) {
-                RETURN (false);
-            }
-            if (((unsigned INT *)cp1)[2] != ((unsigned INT *)(cp1+addrDelta))[2]) {
-                RETURN (false);
-            }
-            if (((unsigned INT *)cp1)[3] != ((unsigned INT *)(cp1+addrDelta))[3]) {
-                RETURN (false);
-            }
-            l1 -= sizeof(unsigned INT)*4;
-            cp1 += sizeof(unsigned INT)*4;
-        }
-        while (l1 >= sizeof(unsigned INT)) {
-            if (*((unsigned INT *)cp1) != *((unsigned INT *)(cp1+addrDelta))) {
-                RETURN (false);
-            }
-            l1 -= sizeof(unsigned INT);
-            cp1 += sizeof(unsigned INT);
-        }
-        if (l1 >= sizeof(unsigned short)) {
-            if (*((unsigned short *)cp1) != *((unsigned short *)(cp1+addrDelta))) {
-                RETURN (false);
-            }
-            l1 -= sizeof(unsigned short);
-            cp1 += sizeof(unsigned short);
-        }
-        while (l1) {
-            if (*cp1 != *(cp1+addrDelta)) {
-                RETURN (false);
-            }
-            l1--;
-            cp1++;
-        }
-
-        RETURN (true);
+	l2 = __byteArraySize(s);
+	l1 = __byteArraySize(self);
+	if (l1 != l2) {
+	    RETURN ( false );
+	}
+
+	cp1 = __byteArrayVal(self);
+	cp2 = __byteArrayVal(s);
+
+	/*
+	 * care for instances of subclasses ...
+	 */
+	if (cls != ByteArray) {
+	    int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+
+	    cp2 += n;
+	    cp1 += n;
+	    l1 -= n;
+	}
+
+	addrDelta = cp2 - cp1;
+	while (l1 >= (sizeof(unsigned INT) * 4)) {
+	    if (((unsigned INT *)cp1)[0] != ((unsigned INT *)(cp1+addrDelta))[0]) {
+		RETURN (false);
+	    }
+	    if (((unsigned INT *)cp1)[1] != ((unsigned INT *)(cp1+addrDelta))[1]) {
+		RETURN (false);
+	    }
+	    if (((unsigned INT *)cp1)[2] != ((unsigned INT *)(cp1+addrDelta))[2]) {
+		RETURN (false);
+	    }
+	    if (((unsigned INT *)cp1)[3] != ((unsigned INT *)(cp1+addrDelta))[3]) {
+		RETURN (false);
+	    }
+	    l1 -= sizeof(unsigned INT)*4;
+	    cp1 += sizeof(unsigned INT)*4;
+	}
+	while (l1 >= sizeof(unsigned INT)) {
+	    if (*((unsigned INT *)cp1) != *((unsigned INT *)(cp1+addrDelta))) {
+		RETURN (false);
+	    }
+	    l1 -= sizeof(unsigned INT);
+	    cp1 += sizeof(unsigned INT);
+	}
+	if (l1 >= sizeof(unsigned short)) {
+	    if (*((unsigned short *)cp1) != *((unsigned short *)(cp1+addrDelta))) {
+		RETURN (false);
+	    }
+	    l1 -= sizeof(unsigned short);
+	    cp1 += sizeof(unsigned short);
+	}
+	while (l1) {
+	    if (*cp1 != *(cp1+addrDelta)) {
+		RETURN (false);
+	    }
+	    l1--;
+	    cp1++;
+	}
+
+	RETURN (true);
     }
 %}.
     ^ super = aByteArray
@@ -1040,9 +1040,9 @@
     ^ (LargeInteger digitBytes:self MSB:true) normalize
 
     "
-        #[ 2 ] asInteger hexPrintString
-        #[ 16r1 16r2 ] asInteger hexPrintString
-        #[4 0 0 0 0 0 0 0] asInteger hexPrintString
+	#[ 2 ] asInteger hexPrintString
+	#[ 16r1 16r2 ] asInteger hexPrintString
+	#[4 0 0 0 0 0 0 0] asInteger hexPrintString
     "
 !
 
@@ -1053,10 +1053,10 @@
     ^ (LargeInteger digitBytes:self MSB:isMSBFirst) normalize
 
     "
-        (#[ 2 ] asIntegerMSB:true) hexPrintString
-        (#[ 16r1 16r2 ] asIntegerMSB:true) hexPrintString
-        (#[ 16r1 16r2 ] asIntegerMSB:false) hexPrintString
-        (#[4 0 0 0 0 0 0 0] asIntegerMSB:true) hexPrintString
+	(#[ 2 ] asIntegerMSB:true) hexPrintString
+	(#[ 16r1 16r2 ] asIntegerMSB:true) hexPrintString
+	(#[ 16r1 16r2 ] asIntegerMSB:false) hexPrintString
+	(#[4 0 0 0 0 0 0 0] asIntegerMSB:true) hexPrintString
     "
 !
 
@@ -1084,44 +1084,44 @@
     stop := self size.
 
     stop > 100 ifTrue:[
-        "/ cg:
-        "/ initial lineBreak
-        outStream cr.
+	"/ cg:
+	"/ initial lineBreak
+	outStream cr.
     ].
     cpl := 0.
 
     [index <= stop] whileTrue:[
-        "take 3 source bytes"
-        n := (self at:index) bitShift:16.
-        (index < stop) ifTrue:[
-            nextIndex := index + 1.
-            n := n bitOr:((self at:nextIndex) bitShift:8).
-            (nextIndex < stop) ifTrue:[
-                n := n bitOr:(self at:(index + 2)).
-            ].
-        ].
-        index := index + 3.
-
-        "took me a while to find that one out ..."
-        n := n bitXor:16r820820.
-
-        outStream nextPut:(Character value:((n bitShift:-18) bitAnd:16r3F) + 32).
-        outStream nextPut:(Character value:((n bitShift:-12) bitAnd:16r3F) + 32).
-        outStream nextPut:(Character value:((n bitShift:-6) bitAnd:16r3F) + 32).
-        outStream nextPut:(Character value:(n bitAnd:16r3F) + 32).
-
-        "/ cg:
-        "/ lineBreak after every 120 characters
-        "/ fromPackedString will ignore those
-        cpl := cpl + 4.
-        cpl >= 120 ifTrue:[
-            outStream cr.
-            cpl := 0.
-        ].
+	"take 3 source bytes"
+	n := (self at:index) bitShift:16.
+	(index < stop) ifTrue:[
+	    nextIndex := index + 1.
+	    n := n bitOr:((self at:nextIndex) bitShift:8).
+	    (nextIndex < stop) ifTrue:[
+		n := n bitOr:(self at:(index + 2)).
+	    ].
+	].
+	index := index + 3.
+
+	"took me a while to find that one out ..."
+	n := n bitXor:16r820820.
+
+	outStream nextPut:(Character value:((n bitShift:-18) bitAnd:16r3F) + 32).
+	outStream nextPut:(Character value:((n bitShift:-12) bitAnd:16r3F) + 32).
+	outStream nextPut:(Character value:((n bitShift:-6) bitAnd:16r3F) + 32).
+	outStream nextPut:(Character value:(n bitAnd:16r3F) + 32).
+
+	"/ cg:
+	"/ lineBreak after every 120 characters
+	"/ fromPackedString will ignore those
+	cpl := cpl + 4.
+	cpl >= 120 ifTrue:[
+	    outStream cr.
+	    cpl := 0.
+	].
     ].
     (mod := stop \\ 3) ~~ 0 ifTrue:[
-        outStream backStep.
-        outStream nextPut:(Character value:(mod + 96)).
+	outStream backStep.
+	outStream nextPut:(Character value:(mod + 96)).
     ].
     ^ outStream contents
 
@@ -1160,7 +1160,7 @@
     |cls|
 
     ((cls := self class) == ByteArray or:[cls == ImmutableByteArray]) ifTrue:[
-        ^ self
+	^ self
     ].
     ^ super literalArrayEncoding
 
@@ -1195,79 +1195,79 @@
 
     if (__isByteArrayLike(self)
      && __bothSmallInteger(start, stop)) {
-        len = __byteArraySize(self);
-        index1 = __intVal(start);
-        index2 = __intVal(stop);
-
-        if ((index1 <= index2) && (index1 > 0)) {
-            if (index2 <= len) {
-                count = index2 - index1 + 1;
-                __PROTECT_CONTEXT__
-                sz = OHDR_SIZE + count;
-                __qNew(newByteArray, sz);       /* OBJECT ALLOCATION */
-                __UNPROTECT_CONTEXT__
-                if (newByteArray != nil) {
-                    __InstPtr(newByteArray)->o_class = ByteArray;
-                    __qSTORE(newByteArray, ByteArray);
-                    dstp = __ByteArrayInstPtr(newByteArray)->ba_element;
-                    srcp = __ByteArrayInstPtr(self)->ba_element + index1 - 1;
+	len = __byteArraySize(self);
+	index1 = __intVal(start);
+	index2 = __intVal(stop);
+
+	if ((index1 <= index2) && (index1 > 0)) {
+	    if (index2 <= len) {
+		count = index2 - index1 + 1;
+		__PROTECT_CONTEXT__
+		sz = OHDR_SIZE + count;
+		__qNew(newByteArray, sz);       /* OBJECT ALLOCATION */
+		__UNPROTECT_CONTEXT__
+		if (newByteArray != nil) {
+		    __InstPtr(newByteArray)->o_class = ByteArray;
+		    __qSTORE(newByteArray, ByteArray);
+		    dstp = __ByteArrayInstPtr(newByteArray)->ba_element;
+		    srcp = __ByteArrayInstPtr(self)->ba_element + index1 - 1;
 
 #ifdef bcopy4
-                    if (((unsigned INT)srcp & 3) == ((unsigned INT)dstp & 3)) {
-                        int nW;
-
-                        /* copy unaligned part */
-                        while (count && (((unsigned INT)srcp & 3) != 0)) {
-                            *dstp++ = *srcp++;
-                            count--;
-                        }
-                        if (count) {
-                            /* copy aligned part */
-                            nW = count >> 2;
-                            if (count & 3) {
-                                nW++;
-                            }
-                            bcopy4(srcp, dstp, nW);
-                        }
-                        RETURN ( newByteArray );
-                    }
+		    if (((unsigned INT)srcp & 3) == ((unsigned INT)dstp & 3)) {
+			int nW;
+
+			/* copy unaligned part */
+			while (count && (((unsigned INT)srcp & 3) != 0)) {
+			    *dstp++ = *srcp++;
+			    count--;
+			}
+			if (count) {
+			    /* copy aligned part */
+			    nW = count >> 2;
+			    if (count & 3) {
+				nW++;
+			    }
+			    bcopy4(srcp, dstp, nW);
+			}
+			RETURN ( newByteArray );
+		    }
 #endif /* bcopy4 */
 #if __POINTER_SIZE__ == 8
-                    if (((unsigned INT)srcp & 7) == ((unsigned INT)dstp & 7)) {
-                        int nW;
-
-                        /* copy unaligned part */
-                        while (count && (((unsigned INT)srcp & 7) != 0)) {
-                            *dstp++ = *srcp++;
-                            count--;
-                        }
-                        /* copy aligned part */
-                        while (count >= 8) {
-                            ((unsigned INT *)dstp)[0] = ((unsigned INT *)srcp)[0];
-                            dstp += 8;
-                            srcp += 8;
-                            count -= 8;
-                        }
-                        /* copy remaining part */
-                        while (count) {
-                            *dstp++ = *srcp++;
-                            count--;
-                        }
-                        RETURN ( newByteArray );
-                    }
+		    if (((unsigned INT)srcp & 7) == ((unsigned INT)dstp & 7)) {
+			int nW;
+
+			/* copy unaligned part */
+			while (count && (((unsigned INT)srcp & 7) != 0)) {
+			    *dstp++ = *srcp++;
+			    count--;
+			}
+			/* copy aligned part */
+			while (count >= 8) {
+			    ((unsigned INT *)dstp)[0] = ((unsigned INT *)srcp)[0];
+			    dstp += 8;
+			    srcp += 8;
+			    count -= 8;
+			}
+			/* copy remaining part */
+			while (count) {
+			    *dstp++ = *srcp++;
+			    count--;
+			}
+			RETURN ( newByteArray );
+		    }
 #endif /* bcopy4 */
 
 #ifdef FAST_MEMCPY
-                    bcopy(srcp, dstp, count);
+		    bcopy(srcp, dstp, count);
 #else
-                    while (count--) {
-                        *dstp++ = *srcp++;
-                    }
+		    while (count--) {
+			*dstp++ = *srcp++;
+		    }
 #endif
-                    RETURN ( newByteArray );
-                }
-            }
-        }
+		    RETURN ( newByteArray );
+		}
+	    }
+	}
     }
 %}.
     "
@@ -1311,33 +1311,33 @@
     unsigned char scratchBuffer[1024], savec;
 
     if (__isByteArrayLike(self) && __bothSmallInteger(start, stop)) {
-        len = __byteArraySize(self);
-        index1 = __intVal(start);
-        index2 = __intVal(stop);
-
-        if ((index1 <= index2) && (index1 > 0) && (index2 <= len)) {
-            count = index2 - index1 + 1;
-            srcp = __ByteArrayInstPtr(self)->ba_element + index1 - 1;
-            if (index2 < len) {
-                /* temporarily stuff in a '\0' */
-                endp = srcp + count + 1;
-                savec = *endp;
-                *endp = '\0';
-                sym = __MKSYMBOL(srcp, 0);
-                /* must refetch endp (in case of a GC */
-                endp = __ByteArrayInstPtr(self)->ba_element + index1 + count;
-                *endp = savec;
-            } else {
-                /* not enough space for '\0', copy the bytes */
-                if (count < sizeof(scratchBuffer)) {
-                    bcopy(srcp, scratchBuffer, count);
-                    scratchBuffer[count] = '\0';
-                    sym = __MKSYMBOL(scratchBuffer, 0);
-                }
-            }
-        }
-        if (sym != nil)
-            RETURN(sym);
+	len = __byteArraySize(self);
+	index1 = __intVal(start);
+	index2 = __intVal(stop);
+
+	if ((index1 <= index2) && (index1 > 0) && (index2 <= len)) {
+	    count = index2 - index1 + 1;
+	    srcp = __ByteArrayInstPtr(self)->ba_element + index1 - 1;
+	    if (index2 < len) {
+		/* temporarily stuff in a '\0' */
+		endp = srcp + count + 1;
+		savec = *endp;
+		*endp = '\0';
+		sym = __MKSYMBOL(srcp, 0);
+		/* must refetch endp (in case of a GC */
+		endp = __ByteArrayInstPtr(self)->ba_element + index1 + count;
+		*endp = savec;
+	    } else {
+		/* not enough space for '\0', copy the bytes */
+		if (count < sizeof(scratchBuffer)) {
+		    bcopy(srcp, scratchBuffer, count);
+		    scratchBuffer[count] = '\0';
+		    sym = __MKSYMBOL(scratchBuffer, 0);
+		}
+	    }
+	}
+	if (sym != nil)
+	    RETURN(sym);
     }
 %}.
     "
@@ -1518,12 +1518,12 @@
      of some logical operation, as specified by the ruleSymbol.
      SourceBytes are fetched starting at sourceOffset.
      Valid rule symbols are:
-        #copy    - trivial;  same as replaceBytesFrom:to:with:startingAt:
-        #bitXor: - xoring;   byte[dI] = byte[dI] bitXor:(srcByte[sI])
-        #bitAnd: - anding;   byte[dI] = byte[dI] bitAnd:(srcByte[sI])
-        #bitOr:  - oring;    byte[dI] = byte[dI] bitOr:(srcByte[sI])
-        #+       - adding;   byte[dI] = (byte[dI] + (srcByte[sI])) mod: 256
-        #-       - subtract; byte[dI] = (byte[dI] - (srcByte[sI])) mod: 256
+	#copy    - trivial;  same as replaceBytesFrom:to:with:startingAt:
+	#bitXor: - xoring;   byte[dI] = byte[dI] bitXor:(srcByte[sI])
+	#bitAnd: - anding;   byte[dI] = byte[dI] bitAnd:(srcByte[sI])
+	#bitOr:  - oring;    byte[dI] = byte[dI] bitOr:(srcByte[sI])
+	#+       - adding;   byte[dI] = (byte[dI] + (srcByte[sI])) mod: 256
+	#-       - subtract; byte[dI] = (byte[dI] - (srcByte[sI])) mod: 256
      Warning: this is a destructive operation - elements in the receiver are overwritten.
     "
 
@@ -1535,130 +1535,130 @@
      && __isSmallInteger(dstStart)
      && __isSmallInteger(dstEnd)
      && __isSmallInteger(sourceStart)) {
-        unsigned char *srcP = __ByteArrayInstPtr(sourceBytes)->ba_element;
-        unsigned char *dstP = __ByteArrayInstPtr(self)->ba_element;
-        int srcLen = __byteArraySize(sourceBytes);
-        int dstLen = __byteArraySize(self);
-        int __srcStart = __intVal(sourceStart);
-        int __dstStart = __intVal(dstStart);
-        int count = __intVal(dstEnd) - __dstStart + 1;
-
-        if ((__dstStart >= 1)
-         && (__srcStart >= 1)
-         && ((__dstStart + count - 1) <= dstLen)
-         && ((__srcStart + count - 1) <= srcLen)) {
-            srcP += __srcStart - 1;
-            dstP += __dstStart - 1;
+	unsigned char *srcP = __ByteArrayInstPtr(sourceBytes)->ba_element;
+	unsigned char *dstP = __ByteArrayInstPtr(self)->ba_element;
+	int srcLen = __byteArraySize(sourceBytes);
+	int dstLen = __byteArraySize(self);
+	int __srcStart = __intVal(sourceStart);
+	int __dstStart = __intVal(dstStart);
+	int count = __intVal(dstEnd) - __dstStart + 1;
+
+	if ((__dstStart >= 1)
+	 && (__srcStart >= 1)
+	 && ((__dstStart + count - 1) <= dstLen)
+	 && ((__srcStart + count - 1) <= srcLen)) {
+	    srcP += __srcStart - 1;
+	    dstP += __dstStart - 1;
 
 #define OP_LOOP_BYTES(OP) \
     while (count > 0) {                                              \
-        *dstP OP (*srcP);                                            \
-        srcP++;                                                      \
-        dstP++;                                                      \
-        count--;                                                     \
+	*dstP OP (*srcP);                                            \
+	srcP++;                                                      \
+	dstP++;                                                      \
+	count--;                                                     \
     }
 
 #define OP_LOOP(OP) \
     while (count >= 16) {                                            \
-        ((unsigned int *)dstP)[0] OP (((unsigned int *)srcP)[0]);    \
-        ((unsigned int *)dstP)[1] OP (((unsigned int *)srcP)[1]);    \
-        ((unsigned int *)dstP)[2] OP (((unsigned int *)srcP)[2]);    \
-        ((unsigned int *)dstP)[3] OP (((unsigned int *)srcP)[3]);    \
-        srcP += 16;                                                  \
-        dstP += 16;                                                  \
-        count -= 16;                                                 \
+	((unsigned int *)dstP)[0] OP (((unsigned int *)srcP)[0]);    \
+	((unsigned int *)dstP)[1] OP (((unsigned int *)srcP)[1]);    \
+	((unsigned int *)dstP)[2] OP (((unsigned int *)srcP)[2]);    \
+	((unsigned int *)dstP)[3] OP (((unsigned int *)srcP)[3]);    \
+	srcP += 16;                                                  \
+	dstP += 16;                                                  \
+	count -= 16;                                                 \
     }                                                                \
     while (count >= 4) {                                             \
-        ((unsigned int *)dstP)[0] OP (((unsigned int *)srcP)[0]);    \
-        srcP += 4;                                                   \
-        dstP += 4;                                                   \
-        count -= 4;                                                  \
+	((unsigned int *)dstP)[0] OP (((unsigned int *)srcP)[0]);    \
+	srcP += 4;                                                   \
+	dstP += 4;                                                   \
+	count -= 4;                                                  \
     }                                                                \
     while (count > 0) {                                              \
-        *dstP OP (*srcP);                                            \
-        srcP++;                                                      \
-        dstP++;                                                      \
-        count--;                                                     \
+	*dstP OP (*srcP);                                            \
+	srcP++;                                                      \
+	dstP++;                                                      \
+	count--;                                                     \
     }
 
 
-            if (ruleSymbol == @symbol(bitXor:)) {
-                OP_LOOP( ^= )
-                RETURN (self);
-            }
-            if (ruleSymbol == @symbol(bitXorNot:)) {
-                OP_LOOP( ^=~ )
-                RETURN (self);
-            }
-            if (ruleSymbol == @symbol(bitAnd:)) {
-                OP_LOOP( &= )
-                RETURN (self);
-            }
-            if (ruleSymbol == @symbol(bitAndNot:)) {
-                OP_LOOP( &=~ )
-                RETURN (self);
-            }
-            if (ruleSymbol == @symbol(bitOr:)) {
-                OP_LOOP( |= )
-                RETURN (self);
-            }
-            if (ruleSymbol == @symbol(bitOrNot:)) {
-                OP_LOOP( |=~ )
-                RETURN (self);
-            }
-            if (ruleSymbol == @symbol(copy)) {
-                OP_LOOP( = )
-                RETURN (self);
-            }
-            if (ruleSymbol == @symbol(copyNot)) {
-                OP_LOOP( =~ )
-                RETURN (self);
-            }
-            if (ruleSymbol == @symbol(+)) {
-                OP_LOOP_BYTES( += )
-                RETURN (self);
-            }
-            if (ruleSymbol == @symbol(-)) {
-                OP_LOOP_BYTES( -= )
-                RETURN (self);
-            }
-        }
+	    if (ruleSymbol == @symbol(bitXor:)) {
+		OP_LOOP( ^= )
+		RETURN (self);
+	    }
+	    if (ruleSymbol == @symbol(bitXorNot:)) {
+		OP_LOOP( ^=~ )
+		RETURN (self);
+	    }
+	    if (ruleSymbol == @symbol(bitAnd:)) {
+		OP_LOOP( &= )
+		RETURN (self);
+	    }
+	    if (ruleSymbol == @symbol(bitAndNot:)) {
+		OP_LOOP( &=~ )
+		RETURN (self);
+	    }
+	    if (ruleSymbol == @symbol(bitOr:)) {
+		OP_LOOP( |= )
+		RETURN (self);
+	    }
+	    if (ruleSymbol == @symbol(bitOrNot:)) {
+		OP_LOOP( |=~ )
+		RETURN (self);
+	    }
+	    if (ruleSymbol == @symbol(copy)) {
+		OP_LOOP( = )
+		RETURN (self);
+	    }
+	    if (ruleSymbol == @symbol(copyNot)) {
+		OP_LOOP( =~ )
+		RETURN (self);
+	    }
+	    if (ruleSymbol == @symbol(+)) {
+		OP_LOOP_BYTES( += )
+		RETURN (self);
+	    }
+	    if (ruleSymbol == @symbol(-)) {
+		OP_LOOP_BYTES( -= )
+		RETURN (self);
+	    }
+	}
     }
 #undef OP_LOOP_BYTES
 #undef OP_LOOP
 
 %}.
     ruleSymbol == #copy ifTrue:[
-        self replaceFrom:dstStart to:dstEnd with:sourceBytes startingAt:sourceStart.
-        ^ self
+	self replaceFrom:dstStart to:dstEnd with:sourceBytes startingAt:sourceStart.
+	^ self
     ].
 
     srcIdx := sourceStart.
     dstStart to:dstEnd do:[:dstIdx |
-        self at:dstIdx put:((self at:dstIdx) perform:ruleSymbol with:(sourceBytes at:srcIdx)).
-        srcIdx := srcIdx + 1.
+	self at:dstIdx put:((self at:dstIdx) perform:ruleSymbol with:(sourceBytes at:srcIdx)).
+	srcIdx := srcIdx + 1.
     ].
 
     "
      #[1 2 3 4 5 6 7 8]
-        bitBlitBytesFrom:1 to:3 with:#[1 2 3 4 5 6 7 8] startingAt:1 rule:#bitXor:
+	bitBlitBytesFrom:1 to:3 with:#[1 2 3 4 5 6 7 8] startingAt:1 rule:#bitXor:
      #[1 2 3 4 5 6 7 8]
-        bitBlitBytesFrom:1 to:8 with:#[1 2 3 4 5 6 7 8] startingAt:1 rule:#bitXor:
+	bitBlitBytesFrom:1 to:8 with:#[1 2 3 4 5 6 7 8] startingAt:1 rule:#bitXor:
      #[1 2 3 4 5 6 7 8]
-        bitBlitBytesFrom:1 to:8 with:#[1 1 1 1 1 1 1 1] startingAt:1 rule:#bitAnd:
+	bitBlitBytesFrom:1 to:8 with:#[1 1 1 1 1 1 1 1] startingAt:1 rule:#bitAnd:
      #[1 2 3 4 5 6 7 8]
-        bitBlitBytesFrom:1 to:8 with:#[1 2 3 4 5 6 7 8] startingAt:1 rule:#+
+	bitBlitBytesFrom:1 to:8 with:#[1 2 3 4 5 6 7 8] startingAt:1 rule:#+
      #[255 0 0 0 0 0 0 0]
-        bitBlitBytesFrom:1 to:8 with:#[1 2 3 4 5 6 7 8] startingAt:1 rule:#+
+	bitBlitBytesFrom:1 to:8 with:#[1 2 3 4 5 6 7 8] startingAt:1 rule:#+
      #[1 2 3 4 5 6 7 8]
-        bitBlitBytesFrom:1 to:4 with:#[1 1 1 1 1 1 1 1] startingAt:1 rule:#+
+	bitBlitBytesFrom:1 to:4 with:#[1 1 1 1 1 1 1 1] startingAt:1 rule:#+
      #[1 2 3 4 5 6 7 8]
-        bitBlitBytesFrom:1 to:4 with:#[1 1 1 1 2 2 2 2] startingAt:5 rule:#+
+	bitBlitBytesFrom:1 to:4 with:#[1 1 1 1 2 2 2 2] startingAt:5 rule:#+
      #[1 2 3 4 5 6 7 8]
-        bitBlitBytesFrom:1 to:4 with:#[1 1 1 1 2 2 2 2] startingAt:5 rule:#copyNot
+	bitBlitBytesFrom:1 to:4 with:#[1 1 1 1 2 2 2 2] startingAt:5 rule:#copyNot
 
      #[1 2 3 4 5 6 7 8]
-        bitBlitBytesFrom:1 to:8 with:(1 to:8) startingAt:1 rule:#+
+	bitBlitBytesFrom:1 to:8 with:(1 to:8) startingAt:1 rule:#+
     "
 !
 
@@ -2221,7 +2221,7 @@
 reverse
     "reverse the order of my elements inplace -
      WARNING: this is a destructive operation, which modifies the receiver.
-              Please use reversed (with a d) for a functional version.
+	      Please use reversed (with a d) for a functional version.
      Written as a primitive for speed on image manipulations (mirror)"
 
 %{  /* NOCONTEXT */
@@ -2232,98 +2232,98 @@
     OBJ cls;
 
     if (__qClass(self) == @global(ByteArray)) {
-        cnt = __byteArraySize(self);
-        p1 = __ByteArrayInstPtr(self)->ba_element;
-        p2 = p1 + cnt - 1;
+	cnt = __byteArraySize(self);
+	p1 = __ByteArrayInstPtr(self)->ba_element;
+	p2 = p1 + cnt - 1;
 
 #if defined(__BSWAP)
-        /*
-         * can we use the bswap instruction ?
-         * notice - not all CPUs have it (the HAS_BSWAP checks this).
-         */
-        if (__HAS_BSWAP()
-         && ((cnt & 3) == 0)) {
-            unsigned int *ip1, *ip2;
-
-            ip1 = (unsigned int *)p1;
-            ip2 = (unsigned int *)(p2 - 3);
-
-            ip2 -= 7;
-            while (ip1 <= ip2) {
-                int t1, t2;
-
-                t1 = ip1[0];
-                t2 = ip2[7];
-                ip2[7] = __BSWAP(t1);
-                ip1[0] = __BSWAP(t2);
-
-                t1 = ip1[1];
-                t2 = ip2[6];
-                ip2[6] = __BSWAP(t1);
-                ip1[1] = __BSWAP(t2);
-
-                t1 = ip1[2];
-                t2 = ip2[5];
-                ip2[5] = __BSWAP(t1);
-                ip1[2] = __BSWAP(t2);
-
-                t1 = ip1[3];
-                t2 = ip2[4];
-                ip2[4] = __BSWAP(t1);
-                ip1[3] = __BSWAP(t2);
-
-                ip1 += 4;
-                ip2 -= 4;
-            }
-            ip2 += 7;
-
-            while (ip1 < ip2) {
-                int t;
-
-                t = __BSWAP(*ip1);
-                *ip1++ = __BSWAP(*ip2);
-                *ip2-- = t;
-            }
-
-            if (ip1 == ip2) {
-                int t;
-                t = *ip1;
-                t = __BSWAP(t);
-                *ip1 = t;
-            }
-            RETURN ( self );
-        }
+	/*
+	 * can we use the bswap instruction ?
+	 * notice - not all CPUs have it (the HAS_BSWAP checks this).
+	 */
+	if (__HAS_BSWAP()
+	 && ((cnt & 3) == 0)) {
+	    unsigned int *ip1, *ip2;
+
+	    ip1 = (unsigned int *)p1;
+	    ip2 = (unsigned int *)(p2 - 3);
+
+	    ip2 -= 7;
+	    while (ip1 <= ip2) {
+		int t1, t2;
+
+		t1 = ip1[0];
+		t2 = ip2[7];
+		ip2[7] = __BSWAP(t1);
+		ip1[0] = __BSWAP(t2);
+
+		t1 = ip1[1];
+		t2 = ip2[6];
+		ip2[6] = __BSWAP(t1);
+		ip1[1] = __BSWAP(t2);
+
+		t1 = ip1[2];
+		t2 = ip2[5];
+		ip2[5] = __BSWAP(t1);
+		ip1[2] = __BSWAP(t2);
+
+		t1 = ip1[3];
+		t2 = ip2[4];
+		ip2[4] = __BSWAP(t1);
+		ip1[3] = __BSWAP(t2);
+
+		ip1 += 4;
+		ip2 -= 4;
+	    }
+	    ip2 += 7;
+
+	    while (ip1 < ip2) {
+		int t;
+
+		t = __BSWAP(*ip1);
+		*ip1++ = __BSWAP(*ip2);
+		*ip2-- = t;
+	    }
+
+	    if (ip1 == ip2) {
+		int t;
+		t = *ip1;
+		t = __BSWAP(t);
+		*ip1 = t;
+	    }
+	    RETURN ( self );
+	}
 #endif /* __i386__ && __GNUC__ */
 
-        p2 -= 7;
-        while (p1 <= p2) {
-            t = p1[0];
-            p1[0] = p2[7];
-            p2[7] = t;
-
-            t = p1[1];
-            p1[1] = p2[6];
-            p2[6] = t;
-
-            t = p1[2];
-            p1[2] = p2[5];
-            p2[5] = t;
-
-            t = p1[3];
-            p1[3] = p2[4];
-            p2[4] = t;
-
-            p1 += 4;
-            p2 -= 4;
-        }
-        p2 += 7;
-
-        while (p1 < p2) {
-            t = *p1;
-            *p1++ = *p2;
-            *p2-- = t;
-        }
-        RETURN ( self );
+	p2 -= 7;
+	while (p1 <= p2) {
+	    t = p1[0];
+	    p1[0] = p2[7];
+	    p2[7] = t;
+
+	    t = p1[1];
+	    p1[1] = p2[6];
+	    p2[6] = t;
+
+	    t = p1[2];
+	    p1[2] = p2[5];
+	    p2[5] = t;
+
+	    t = p1[3];
+	    p1[3] = p2[4];
+	    p2[4] = t;
+
+	    p1 += 4;
+	    p2 -= 4;
+	}
+	p2 += 7;
+
+	while (p1 < p2) {
+	    t = *p1;
+	    *p1++ = *p2;
+	    *p2-- = t;
+	}
+	RETURN ( self );
     }
 %}.
     ^ super reverse
@@ -2343,32 +2343,32 @@
      (1 to:255) asByteArray reverse
 
      1 to:1024 do:[:i|
-        |bytes test rBytes|
-
-        bytes := ((1 to:i) asArray collect:[:i | i bitAnd:255]) asByteArray.
-        test := ((i to:1 by:-1) asArray collect:[:i | i bitAnd:255]) asByteArray.
-        rBytes := bytes copy.
-        rBytes reverse ~= test ifTrue:[
-            self halt
-        ].
-        rBytes := bytes copy.
-        rBytes reverse reverse ~= bytes ifTrue:[
-            self halt
-        ]
+	|bytes test rBytes|
+
+	bytes := ((1 to:i) asArray collect:[:i | i bitAnd:255]) asByteArray.
+	test := ((i to:1 by:-1) asArray collect:[:i | i bitAnd:255]) asByteArray.
+	rBytes := bytes copy.
+	rBytes reverse ~= test ifTrue:[
+	    self halt
+	].
+	rBytes := bytes copy.
+	rBytes reverse reverse ~= bytes ifTrue:[
+	    self halt
+	]
      ].
 
      Time millisecondsToRun:[
-        10000000 timesRepeat:[
-            #[1 2 3 4 5 6 7 8] reverse
-        ]
+	10000000 timesRepeat:[
+	    #[1 2 3 4 5 6 7 8] reverse
+	]
      ]
 
      |b|
      b := (0 to:255) asByteArray.
      Time millisecondsToRun:[
-        10000000 timesRepeat:[
-            b reverse
-        ]
+	10000000 timesRepeat:[
+	    b reverse
+	]
      ]
     "
 !
@@ -2424,16 +2424,16 @@
     unsigned int t;
 
     if (__qClass(self) == @global(ByteArray) && __bothSmallInteger(i1, i2)) {
-        __i1 = __intVal(i1) - 1;
-        __i2 = __intVal(i2) - 1;
-        cnt = __byteArraySize(self);
-        p = __ByteArrayInstPtr(self)->ba_element;
-        if (__i1 < cnt && __i2 < cnt) {
-            t = p[__i1];
-            p[__i1] = p[__i2];
-            p[__i2] = t;
-        }
-        RETURN ( self );
+	__i1 = __intVal(i1) - 1;
+	__i2 = __intVal(i2) - 1;
+	cnt = __byteArraySize(self);
+	p = __ByteArrayInstPtr(self)->ba_element;
+	if (__i1 < cnt && __i2 < cnt) {
+	    t = p[__i1];
+	    p[__i1] = p[__i2];
+	    p[__i2] = t;
+	}
+	RETURN ( self );
     }
 %}.
     ^ super swapIndex:i1 and:i2 "/ rubbish - there is no one currently
@@ -2571,9 +2571,9 @@
     "print as hex string, eg: 'FF:02:43'"
 
     self do:[:byte|
-        byte printOn:aStream base:16 size:2 fill:$0.
+	byte printOn:aStream base:16 size:2 fill:$0.
     ] separatedBy:[
-        aSeparatorStringOrCharacter printOn:aStream
+	aSeparatorStringOrCharacter printOn:aStream
     ].
 
     "
@@ -2589,7 +2589,7 @@
 
     s := '' writeStream.
     self do:[:byte|
-        byte printOn:s base:16 size:2 fill:$0.
+	byte printOn:s base:16 size:2 fill:$0.
     ].
     ^ s contents.
 
@@ -2623,13 +2623,13 @@
     |cls|
 
     "/ care for subclasses
-    ((cls := self class) == ByteArray or:[cls == ImmutableByteArray]) ifTrue:[    
-        aStream nextPutAll:'#['.
-        self
-            do:[:byte | byte printOn:aStream]
-            separatedBy:[aStream space].
-        aStream nextPut:$].
-        ^ self
+    ((cls := self class) == ByteArray or:[cls == ImmutableByteArray]) ifTrue:[
+	aStream nextPutAll:'#['.
+	self
+	    do:[:byte | byte printOn:aStream]
+	    separatedBy:[aStream space].
+	aStream nextPut:$].
+	^ self
     ].
     ^ super printOn:aStream
 
@@ -2670,13 +2670,13 @@
     |cls|
 
     ((cls := self class) == ByteArray or:[cls == ImmutableByteArray]) ifTrue:[
-        "/ care for subclasses
-        aStream nextPutAll:'#['.
-        self
-            do:[:byte | byte printOn:aStream base:radix showRadix:showRadix]
-            separatedBy:[aStream space].
-        aStream nextPut:$].
-        ^ self
+	"/ care for subclasses
+	aStream nextPutAll:'#['.
+	self
+	    do:[:byte | byte printOn:aStream base:radix showRadix:showRadix]
+	    separatedBy:[aStream space].
+	aStream nextPut:$].
+	^ self
     ].
     ^ self printOn:aStream
 
@@ -2699,14 +2699,14 @@
 
     |cls|
 
-    ((cls := self class) == ByteArray or:[cls == ImmutableByteArray]) ifTrue:[    
-        "/ care for subclasses
-        aStream nextPut:$[.
-        self
-            do:[:byte | byte storeOn:aStream]
-            separatedBy:[aStream space].
-        aStream nextPut:$].
-        ^ self
+    ((cls := self class) == ByteArray or:[cls == ImmutableByteArray]) ifTrue:[
+	"/ care for subclasses
+	aStream nextPut:$[.
+	self
+	    do:[:byte | byte storeOn:aStream]
+	    separatedBy:[aStream space].
+	aStream nextPut:$].
+	^ self
     ].
     super storeArrayElementOn:aStream
 
@@ -2728,14 +2728,14 @@
 
     |cls|
 
-    ((cls := self class) == ByteArray or:[cls == ImmutableByteArray]) ifTrue:[    
-        "/ care for subclasses
-        aStream nextPutAll:'#['.
-        self
-            do:[:byte | byte storeOn:aStream]
-            separatedBy:[aStream space].
-        aStream nextPutAll:']'.
-        ^ self
+    ((cls := self class) == ByteArray or:[cls == ImmutableByteArray]) ifTrue:[
+	"/ care for subclasses
+	aStream nextPutAll:'#['.
+	self
+	    do:[:byte | byte storeOn:aStream]
+	    separatedBy:[aStream space].
+	aStream nextPutAll:']'.
+	^ self
     ].
     ^ super storeOn:aStream
 
@@ -2813,29 +2813,29 @@
     INT icounts[256];
 
     if (__isByteArrayLike(self) && __isArray(counts)) {
-        /*
-         * zero counts
-         */
-        for (index=0; index<256; index++) {
-            icounts[index] = 0;
-        }
-
-        /*
-         * count
-         */
-        nByte = __qSize(self) - OHDR_SIZE;
-        cp = &(__ByteArrayInstPtr(self)->ba_element[0]);
-        while (nByte--) {
-            icounts[*cp++]++;
-        }
-
-        /*
-         * make it real counts
-         */
-        for (index=0; index<256; index++) {
-            __ArrayInstPtr(counts)->a_element[index] = __mkSmallInteger(icounts[index]);
-        }
-        RETURN ( counts );
+	/*
+	 * zero counts
+	 */
+	for (index=0; index<256; index++) {
+	    icounts[index] = 0;
+	}
+
+	/*
+	 * count
+	 */
+	nByte = __qSize(self) - OHDR_SIZE;
+	cp = &(__ByteArrayInstPtr(self)->ba_element[0]);
+	while (nByte--) {
+	    icounts[*cp++]++;
+	}
+
+	/*
+	 * make it real counts
+	 */
+	for (index=0; index<256; index++) {
+	    __ArrayInstPtr(counts)->a_element[index] = __mkSmallInteger(icounts[index]);
+	}
+	RETURN ( counts );
     }
 %}
 .
@@ -2858,8 +2858,8 @@
     REGISTER int len;
     OBJ result;
     union {
-        unsigned char flags[256];
-        int toForceAlignmentOfFlags;
+	unsigned char flags[256];
+	int toForceAlignmentOfFlags;
     } f;
 
 #ifdef TO_BE_MEASURED
@@ -2867,53 +2867,53 @@
 #endif
 
     if (__isByteArrayLike(self)) {
-        memset(f.flags, 0, sizeof(f.flags));
-        len = __qSize(self) - OHDR_SIZE;
-        cp = &(__ByteArrayInstPtr(self)->ba_element[0]);
-
-        /* for each used byte, set flag */
-        while (len > 0) {
+	memset(f.flags, 0, sizeof(f.flags));
+	len = __qSize(self) - OHDR_SIZE;
+	cp = &(__ByteArrayInstPtr(self)->ba_element[0]);
+
+	/* for each used byte, set flag */
+	while (len > 0) {
 #ifdef TO_BE_MEASURED
-            unsigned  byte;
-
-            byte = *cp;
-            if (! f.flags[byte]) {
-                f.flags[byte] = 1;
-                coverage++;
-                if (coverage == 256) {
-                    /* no need to scan rest */
-                    break;
-                }
-            }
+	    unsigned  byte;
+
+	    byte = *cp;
+	    if (! f.flags[byte]) {
+		f.flags[byte] = 1;
+		coverage++;
+		if (coverage == 256) {
+		    /* no need to scan rest */
+		    break;
+		}
+	    }
 #else
-            f.flags[*cp] = 1;
+	    f.flags[*cp] = 1;
 #endif
-            cp++;
-            len--;
-        }
-
-        /* count 1's */
-        len = 0;
-        for (cp=f.flags, endp=f.flags+256; cp < endp;) {
-            if ( *((unsigned int *)cp)) {
-                if (cp[0]) len++;
-                if (cp[1]) len++;
-                if (cp[2]) len++;
-                if (cp[3]) len++;
-            }
-            cp += 4;
-        }
-
-        /* create ByteArray of used values */
-        result = __BYTEARRAY_UNINITIALIZED_NEW_INT(len);
-        if (result) {
-            cp = __ByteArrayInstPtr(result)->ba_element;
-            for (len=0; len < 256; len++) {
-                if (f.flags[len])
-                    *cp++ = len;
-            }
-            RETURN ( result );
-        }
+	    cp++;
+	    len--;
+	}
+
+	/* count 1's */
+	len = 0;
+	for (cp=f.flags, endp=f.flags+256; cp < endp;) {
+	    if ( *((unsigned int *)cp)) {
+		if (cp[0]) len++;
+		if (cp[1]) len++;
+		if (cp[2]) len++;
+		if (cp[3]) len++;
+	    }
+	    cp += 4;
+	}
+
+	/* create ByteArray of used values */
+	result = __BYTEARRAY_UNINITIALIZED_NEW_INT(len);
+	if (result) {
+	    cp = __ByteArrayInstPtr(result)->ba_element;
+	    for (len=0; len < 256; len++) {
+		if (f.flags[len])
+		    *cp++ = len;
+	    }
+	    RETURN ( result );
+	}
     }
 %}.
     ^ self asIdentitySet asByteArray
@@ -3005,13 +3005,14 @@
 !ByteArray class methodsFor:'documentation'!
 
 version
-    ^ '$Id: ByteArray.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ByteArray.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/ByteArray.st,v 1.200 2010/03/08 07:42:51 stefan Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/ByteArray.st,v 1.201 2010/04/14 08:33:59 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: ByteArray.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ByteArray.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
+
--- a/CharacterArray.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/CharacterArray.st	Tue May 04 12:50:05 2010 +0100
@@ -1881,10 +1881,10 @@
     |s|
 
     (s := self string) ~~ self ifTrue:[
-	^ s endsWith:aStringOrCharacter
+        ^ s endsWith:aStringOrCharacter
     ].
-    aStringOrCharacter isCharacter ifTrue:[
-	^ self last = aStringOrCharacter
+    (self notEmpty and:[aStringOrCharacter isCharacter]) ifTrue:[
+        ^ self last = aStringOrCharacter
     ].
     ^ super endsWith:aStringOrCharacter
 
@@ -3641,7 +3641,7 @@
     ^ s contents
 
     "
-	'abcdeäöüß' utf8Encoded
+	'abcde' utf8Encoded
     "
 ! !
 
@@ -5817,15 +5817,16 @@
 !CharacterArray class methodsFor:'documentation'!
 
 version
-    ^ '$Id: CharacterArray.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: CharacterArray.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.431 2010/03/08 07:42:41 stefan Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.432 2010/05/03 13:20:52 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: CharacterArray.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: CharacterArray.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 CharacterArray initialize!
+
--- a/Class.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/Class.st	Tue May 04 12:50:05 2010 +0100
@@ -12,34 +12,34 @@
 "{ Package: 'stx:libbasic' }"
 
 ClassDescription subclass:#Class
-	instanceVariableNames:'name category classvars comment subclasses classFilename package
-		revision environment signature attributes'
-	classVariableNames:'DefaultCategoryForSTV DefaultCategoryForVAGE
-		DefaultCategoryForDolphin'
-	poolDictionaries:''
-	category:'Kernel-Classes'
+        instanceVariableNames:'name category classvars comment subclasses classFilename package
+                revision environment signature attributes'
+        classVariableNames:'DefaultCategoryForSTV DefaultCategoryForVAGE
+                DefaultCategoryForDolphin'
+        poolDictionaries:''
+        category:'Kernel-Classes'
 !
 
 Object subclass:#ClassAttributes
-	instanceVariableNames:'primitiveDefinitions primitiveVariables primitiveFunctions
-		sharedPools traitComposition localSelectors'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:Class
+        instanceVariableNames:'primitiveDefinitions primitiveVariables primitiveFunctions
+                sharedPools traitComposition localSelectors'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:Class
 !
 
 Object subclass:#SimulatedClassPool
-	instanceVariableNames:'class'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:Class
+        instanceVariableNames:'class'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:Class
 !
 
 Association subclass:#SimulatedVariableBinding
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:Class::SimulatedClassPool
+        instanceVariableNames:''
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:Class::SimulatedClassPool
 !
 
 !Class class methodsFor:'documentation'!
@@ -377,6 +377,9 @@
      This is private protocol"
 
     SubclassInfo := nil.
+    self allSubInstancesDo:[:cls |
+        cls flushSubclasses
+    ].
 
     "
      Class flushSubclassInfo
@@ -393,7 +396,8 @@
     aClass notNil ifTrue:[
         SubclassInfo notNil ifTrue:[
             SubclassInfo removeKey:aClass ifAbsent:[]
-        ]
+        ].
+        aClass flushSubclasses
     ].
 
     "
@@ -414,22 +418,22 @@
 
     |d|
 
-    SubclassInfo notNil ifTrue:[^ SubclassInfo].
-
-    d := IdentityDictionary new.
-    Smalltalk allClassesDo:[:aClass |
-        |superCls setToAddSubclass|
-
-        superCls := aClass superclass.
-        superCls notNil ifTrue:[
-            setToAddSubclass := d at:superCls ifAbsent:nil.
-            setToAddSubclass isNil ifTrue:[
-                d at:superCls put:(Set with:aClass).
-            ] ifFalse:[
-                setToAddSubclass add:aClass
-            ]
-        ]
-    ].
+"/    SubclassInfo notNil ifTrue:[^ SubclassInfo].
+"/
+"/    d := IdentityDictionary new.
+"/    Smalltalk allClassesDo:[:aClass |
+"/        |superCls setToAddSubclass|
+"/
+"/        superCls := aClass superclass.
+"/        superCls notNil ifTrue:[
+"/            setToAddSubclass := d at:superCls ifAbsent:nil.
+"/            setToAddSubclass isNil ifTrue:[
+"/                d at:superCls put:(Set with:aClass).
+"/            ] ifFalse:[
+"/                setToAddSubclass add:aClass
+"/            ]
+"/        ]
+"/    ].
     SubclassInfo := d.
     ^ d
 
@@ -1592,11 +1596,81 @@
 
     "Created: / 07-12-1995 / 13:16:46 / cg"
     "Modified: / 05-12-2006 / 22:04:26 / cg"
+!
+
+subclasses
+    "return a collection of the direct subclasses of the receiver"
+
+    "/ use cached information (avoid class hierarchy search), if possible
+    subclasses isNil ifTrue:[
+        self updateAllCachedSubclasses.
+        "subclasses may still be nil - obsolete classes may not be updated"
+        ^ subclasses ?#().
+    ].
+    ^ subclasses.
+
+    "
+     Class flushSubclassInfo.
+     Class subclasses.
+     SmallInteger subclasses
+    "
+
+    "Modified: / 30-04-2010 / 11:51:33 / cg"
+!
+
+superclass:aClass
+    "set the superclass - this actually creates a new class,
+     recompiling all methods for the new one. The receiving class stays
+     around anonymously to allow existing instances some life.
+     This may change in the future (adjusting existing instances)"
+
+    |owner ns name|
+
+    "must flush caches since lookup chain changes"
+    ObjectMemory flushCaches.
+
+    "/ for correct recompilation, just create a new class ...
+    "/ but care to avoid a nameSpace change, by giving my
+    "/ full name and answering with Smalltalk to a nameSpace query.
+
+    (owner := self owningClass) notNil ifTrue:[
+        ns := owner.
+        name := self nameWithoutPrefix asSymbol
+    ] ifFalse:[
+        ns := Smalltalk.
+        name := self name
+    ].
+
+    Class classRedefinitionNotification answer:#keep do:[
+        Class nameSpaceQuerySignal 
+            answer:ns
+            do:[
+                aClass
+                    perform:(self definitionSelector)
+                    withArguments:(Array with:name
+                                   with:(self instanceVariableString)
+                                   with:(self classVariableString)
+                                   with:'' "/ pool
+                                   with:(self category)).
+            ]
+    ]
+
+    "Modified: / 20.6.1998 / 18:17:37 / cg"
 ! !
 
 
 !Class methodsFor:'adding & removing'!
 
+removeFromSystem
+    "ST-80 compatibility
+     remove myself from the system"
+
+    Smalltalk removeClass:self.
+    Smalltalk removeKey:name.
+
+    "Created: 6.2.1996 / 11:32:58 / stefan"
+!
+
 unload
     "{ Pragma: +optSpace }"
 
@@ -1672,18 +1746,6 @@
     "Modified: 4.6.1997 / 14:48:02 / cg"
 ! !
 
-!Class methodsFor:'adding/removing'!
-
-removeFromSystem
-    "ST-80 compatibility
-     remove myself from the system"
-
-    Smalltalk removeClass:self.
-    Smalltalk removeKey:name.
-
-    "Created: 6.2.1996 / 11:32:58 / stefan"
-! !
-
 
 !Class methodsFor:'changes management'!
 
@@ -1993,39 +2055,17 @@
      This will only enumerate globally known classes - for anonymous
      behaviors, you have to walk over all instances of Behavior."
 
-    |coll|
-
-    "/ use cached information (avoid class hierarchy search)
-    "/ if possible
-    SubclassInfo isNil ifTrue:[
-        Class subclassInfo   "/ creates SubclassInfo as side effect
-    ].
-    SubclassInfo notNil ifTrue:[
-        coll := SubclassInfo at:self ifAbsent:nil.
-        coll notNil ifTrue:[
-            coll do:aBlock.
-            ^ self
-        ].
+    "/ use cached information (avoid class hierarchy search), if possible
+    subclasses isNil ifTrue:[
+        self updateAllCachedSubclasses
     ].
-
-    coll := OrderedCollection new.
-    Smalltalk allClassesDo:[:aClass |
-        (aClass superclass == self) ifTrue:[
-            coll add:aClass
-        ]
-    ].
-
-    SubclassInfo notNil ifTrue:[
-        SubclassInfo at:self put:coll.
-    ].
-
-    coll do:aBlock.
+    subclasses do:aBlock
 
     "
      Collection subclassesDo:[:c | Transcript showCR:(c name)]
     "
 
-    "Modified: 22.1.1997 / 18:44:01 / cg"
+    "Modified: / 28-04-2010 / 08:51:46 / cg"
 !
 
 withAllPrivateClassesDo:aBlock
@@ -3160,6 +3200,33 @@
     "Modified: / 25.11.1998 / 12:40:31 / cg"
 !
 
+printOutProtocolOn:aPrintStream
+    "{ Pragma: +optSpace }"
+
+    |collectionOfCategories|
+
+    self printOutDefinitionOn:aPrintStream.
+    aPrintStream cr.
+    collectionOfCategories := self class categories asSortedCollection.
+    collectionOfCategories notNil ifTrue:[
+        aPrintStream nextPutLine:'class protocol'.
+        aPrintStream cr.
+        collectionOfCategories do:[:aCategory |
+            self class printOutCategoryProtocol:aCategory on:aPrintStream
+        ]
+    ].
+    collectionOfCategories := self categories asSortedCollection.
+    collectionOfCategories notNil ifTrue:[
+        aPrintStream nextPutLine:'instance protocol'.
+        aPrintStream cr.
+        collectionOfCategories do:[:aCategory |
+            self printOutCategoryProtocol:aCategory on:aPrintStream
+        ]
+    ]
+
+    "Modified: / 25.11.1998 / 12:40:38 / cg"
+!
+
 printSharedPoolNamesOn:aStream indent:indent
     "print the pool names indented and breaking at line end"
 
@@ -3208,6 +3275,10 @@
     attributes := aClassAttributesObject
 !
 
+flushSubclasses
+    subclasses := nil
+!
+
 getAttribute:aKey
     "get an attribute (by symbolic key)"
 
@@ -3249,6 +3320,17 @@
     self classAttributes perform:(key , ':') asSymbol with:aValue
 !
 
+setName:aString
+    "set the classes name - be careful, it will be still
+     in the Smalltalk dictionary - under another key.
+     This is NOT for general use - see renameTo:"
+
+    environment := nil.
+    name := aString
+
+    "Created: 1.4.1997 / 15:46:01 / stefan"
+!
+
 setPrimitiveDefinitions:aString
     "{ Pragma: +optSpace }"
 
@@ -3281,6 +3363,12 @@
     ^ self setAttribute:#sharedPools to:aStringOrCollection
 !
 
+setSubclasses:aCollection
+    subclasses := aCollection
+
+    "Created: / 28-04-2010 / 08:48:49 / cg"
+!
+
 setSuperclass:aClass
     "set the superclass of the receiver.
      this method is for special uses only - there will be no recompilation
@@ -3289,10 +3377,33 @@
      be correct, since no caches are flushed.
      Therefore: do NOT use it; use #superclass: (or flush the caches, at least)."
 
-    superclass ~~ aClass ifTrue:[
-        SubclassInfo := nil.  "/ flush it
-        superclass := aClass
+    superclass := aClass
+
+    "Modified: / 28-04-2010 / 08:49:07 / cg"
+!
+
+updateAllCachedSubclasses
+    |subclassesPerClass|
+
+    subclassesPerClass := Dictionary new.
+    Smalltalk allClassesDo:[:each |
+        |cls superclass|
+
+        cls := each theNonMetaclass.
+        (superclass := each superclass) notNil ifTrue:[
+            (subclassesPerClass at:superclass ifAbsentPut:[Set new]) add:cls
+        ].
+        subclassesPerClass at:cls ifAbsentPut:[Set new].
     ].
+    subclassesPerClass keysAndValuesDo:[:cls :subclasses |
+        cls setSubclasses:(subclasses asArray).
+    ].
+
+    "
+     Class updateAllCachedSubclasses
+    "
+
+    "Created: / 28-04-2010 / 08:47:20 / cg"
 ! !
 
 !Class methodsFor:'private-changes management'!
@@ -3399,35 +3510,6 @@
     "Modified: 9.11.1996 / 00:10:10 / cg"
 ! !
 
-!Class methodsFor:'protocol printOut'!
-
-printOutProtocolOn:aPrintStream
-    "{ Pragma: +optSpace }"
-
-    |collectionOfCategories|
-
-    self printOutDefinitionOn:aPrintStream.
-    aPrintStream cr.
-    collectionOfCategories := self class categories asSortedCollection.
-    collectionOfCategories notNil ifTrue:[
-        aPrintStream nextPutLine:'class protocol'.
-        aPrintStream cr.
-        collectionOfCategories do:[:aCategory |
-            self class printOutCategoryProtocol:aCategory on:aPrintStream
-        ]
-    ].
-    collectionOfCategories := self categories asSortedCollection.
-    collectionOfCategories notNil ifTrue:[
-        aPrintStream nextPutLine:'instance protocol'.
-        aPrintStream cr.
-        collectionOfCategories do:[:aCategory |
-            self printOutCategoryProtocol:aCategory on:aPrintStream
-        ]
-    ]
-
-    "Modified: / 25.11.1998 / 12:40:38 / cg"
-! !
-
 !Class methodsFor:'queries'!
 
 canHaveExtensions
@@ -3654,36 +3736,6 @@
     "Modified: 18.4.1997 / 20:55:34 / cg"
 !
 
-subclasses
-    "return a collection of the direct subclasses of the receiver"
-
-    |newColl|
-
-    "/ use cached information (avoid class hierarchy search)
-    "/ if possible
-
-    SubclassInfo notNil ifTrue:[
-        newColl := SubclassInfo at:self ifAbsent:nil.
-        newColl notNil ifTrue:[^ newColl asOrderedCollection]
-    ].
-
-    newColl := OrderedCollection new.
-    self subclassesDo:[:aClass |
-        newColl add:aClass
-    ].
-    SubclassInfo notNil ifTrue:[
-        SubclassInfo at:self put:newColl.
-    ].
-    ^ newColl
-
-    "
-     Class flushSubclassInfo.
-     Collection subclasses
-    "
-
-    "Modified: 22.1.1997 / 18:43:52 / cg"
-!
-
 wasAutoloaded
     "return true, if this class came into the system via an
      autoload; false otherwise.
@@ -4827,19 +4879,6 @@
     "Created: / 16-08-2009 / 12:57:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
 
-!Class methodsFor:'special accessing'!
-
-setName:aString
-    "set the classes name - be careful, it will be still
-     in the Smalltalk dictionary - under another key.
-     This is NOT for general use - see renameTo:"
-
-    environment := nil.
-    name := aString
-
-    "Created: 1.4.1997 / 15:46:01 / stefan"
-! !
-
 !Class::ClassAttributes class methodsFor:'documentation'!
 
 documentation
@@ -5035,13 +5074,14 @@
 !Class class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Class.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: Class.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/Class.st,v 1.568 2010/04/06 15:33:20 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/Class.st,v 1.573 2010/04/30 09:56:51 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: Class.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: Class.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
+
--- a/ClassBuilder.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/ClassBuilder.st	Tue May 04 12:50:05 2010 +0100
@@ -567,6 +567,9 @@
     newSuperClass := newClass superclass.
     superClassChange := (oldSuperClass ~~ newSuperClass).
 
+    Class flushSubclassInfoFor:oldSuperClass.
+    Class flushSubclassInfoFor:newSuperClass.
+
     oldPoolDictionaries := oldClass sharedPools.
 
     superClassChange ifFalse:[
@@ -591,7 +594,7 @@
 
     "Created: / 26-05-1996 / 11:55:26 / cg"
     "Modified: / 18-03-1999 / 18:23:31 / stefan"
-    "Modified: / 24-09-2007 / 19:31:31 / cg"
+    "Modified: / 26-04-2010 / 23:47:33 / cg"
 !
 
 newSubclassOf:baseClass type:typeOfClass instanceVariables:instanceVariables from:oldClassArg
@@ -1247,7 +1250,8 @@
      (systemBrowsers will react on this, and update their views)"
     oldClass changed:#definition with:newClass.
 
-    Class flushSubclassInfo.
+    Class flushSubclassInfoFor:oldClass.
+    Class flushSubclassInfoFor:newClass.
     self environmentChanged:#classDefinition with:newClass.
 
     ObjectMemory flushCaches.
@@ -1286,8 +1290,8 @@
         ].
     ].
 
-    Class flushSubclassInfoFor:oldSuperClass.
-    Class flushSubclassInfoFor:newSuperClass.
+    oldClass notNil ifTrue:[ Class flushSubclassInfoFor:oldClass superclass].
+    Class flushSubclassInfoFor:newClass superclass.
 
 "/    oldClass notNil ifTrue:[
 "/        "/ since we changed the classes inheritance (from Autoloaded)
@@ -1342,6 +1346,8 @@
             in:(newClass owningClass nameSpace) except:newClass.
     ].
     ^ newClass
+
+    "Modified: / 27-04-2010 / 00:03:42 / cg"
 !
 
 instantiateMetaclass
@@ -1629,7 +1635,7 @@
      create a new class tree, based on the new version
     "
     Smalltalk flushCachedClasses.
-    Class flushSubclassInfoFor:self.
+    Class flushSubclassInfoFor:oldClass.
     allSubclasses do:[:aSubclass |
         |oldSuper|
 
@@ -2214,13 +2220,14 @@
 !ClassBuilder class methodsFor:'documentation'!
 
 version
-    ^ '$Id: ClassBuilder.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ClassBuilder.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/ClassBuilder.st,v 1.90 2010/02/05 12:59:07 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/ClassBuilder.st,v 1.93 2010/04/26 22:03:53 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: ClassBuilder.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ClassBuilder.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
+
--- a/ClassDescription.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/ClassDescription.st	Tue May 04 12:50:05 2010 +0100
@@ -1168,28 +1168,30 @@
     oldMethod := self compiledMethodAt:aSelector.
 
     MethodHistory notNil ifTrue:[
-	oldMethod notNil ifTrue:[
-	    MethodHistory add:(Array with:#methodRemove with:oldMethod).
-	    (MethodHistorySize notNil and:[MethodHistory size > MethodHistorySize]) ifTrue:[
-		MethodHistory removeFirst.
-	    ]
-	]
+        oldMethod notNil ifTrue:[
+            MethodHistory add:(Array with:#methodRemove with:oldMethod).
+            (MethodHistorySize notNil and:[MethodHistory size > MethodHistorySize]) ifTrue:[
+                MethodHistory removeFirst.
+            ]
+        ]
     ].
 
     (super removeSelector:aSelector) ifTrue:[
-	self addChangeRecordForRemoveSelector:aSelector fromOld:oldMethod.
-	"/
-	"/ also notify a change of mySelf;
-	"/
-	self changed:#methodDictionary with:aSelector.
-
-	"/
-	"/ also notify a change of Smalltalk;
-	"/ this allows a dependent of Smalltalk to watch all class
-	"/ changes (no need for observing all classes)
-	"/ - this allows for watchers to find out if its a new method or a method-change
-	"/
-	Smalltalk changed:#methodInClassRemoved with:(Array with:self with:aSelector).
+        self addChangeRecordForRemoveSelector:aSelector fromOld:oldMethod.
+        "/
+        "/ also notify a change of mySelf;
+        "/
+        self changed:#methodDictionary with:aSelector.
+
+        "/
+        "/ also notify a change of Smalltalk;
+        "/ this allows a dependent of Smalltalk to watch all class
+        "/ changes (no need for observing all classes)
+        "/ - this allows for watchers to find out if its a new method or a method-change
+        "/
+        MethodRemoveChangeNotificationParameter notNil ifTrue:[
+            Smalltalk changed:#methodInClassRemoved with:(MethodRemoveChangeNotificationParameter changeClass:self changeSelector:aSelector).
+        ]
     ]
 
     "Modified: 8.1.1997 / 23:03:49 / cg"
@@ -4102,17 +4104,18 @@
 !ClassDescription class methodsFor:'documentation'!
 
 version
-    ^ '$Id: ClassDescription.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ClassDescription.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/ClassDescription.st,v 1.212 2009/12/21 18:59:51 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/ClassDescription.st,v 1.214 2010/04/19 16:46:03 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: ClassDescription.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ClassDescription.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 ClassDescription initialize!
 ClassDescription::MethodRedefinitionNotification initialize!
 ClassDescription::ClassRedefinitionNotification initialize!
+
--- a/DirectoryStream.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/DirectoryStream.st	Tue May 04 12:50:05 2010 +0100
@@ -487,6 +487,23 @@
 
 !DirectoryStream methodsFor:'access-reading'!
 
+contents
+    "answer all of the directory entries as an OrderedCollection"
+
+    |contents|
+
+    contents := OrderedCollection new.
+    [self atEnd] whileFalse:[  
+        |l|
+        l := self nextLine.
+        l isNil ifTrue:[
+            ^ contents
+        ].
+        contents add:l
+    ].
+    ^ contents
+!
+
 nextLine
     "return the next filename as a string"
 
@@ -778,13 +795,14 @@
 !DirectoryStream class methodsFor:'documentation'!
 
 version
-    ^ '$Id: DirectoryStream.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: DirectoryStream.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/DirectoryStream.st,v 1.73 2010/02/09 18:13:24 stefan Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/DirectoryStream.st,v 1.74 2010/04/30 16:48:14 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: DirectoryStream.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: DirectoryStream.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
+
--- a/ExecutableFunction.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/ExecutableFunction.st	Tue May 04 12:50:05 2010 +0100
@@ -239,6 +239,15 @@
     "Modified: / 13.11.1998 / 23:16:32 / cg"
 !
 
+isInstrumented
+    "return true, if this is an instrumented method.
+     False is returned here - this method is redefined in InstrumentedMethod"
+
+    ^ false
+
+    "Created: / 27-04-2010 / 12:26:05 / cg"
+!
+
 isInvalid
     "return true, if this codeObject is invalidated.
      Return false here, to alow alien codeObjects to be handled by the
@@ -404,9 +413,14 @@
 !ExecutableFunction class methodsFor:'documentation'!
 
 version
-    ^ '$Id: ExecutableFunction.st 10487 2009-12-27 19:02:18Z vranyj1 $'
+    ^ '$Id: ExecutableFunction.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_SVN
-    ^ '$Id: ExecutableFunction.st 10487 2009-12-27 19:02:18Z vranyj1 $'
+    ^ '$Id: ExecutableFunction.st 10520 2010-05-04 11:50:05Z vranyj1 $'
+!
+
+version_CVS
+    ^ 'Header: /cvs/stx/stx/libbasic/ExecutableFunction.st,v 1.56 2010/04/27 10:26:12 cg Exp §'
 ! !
+
--- a/ExternalAddress.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/ExternalAddress.st	Tue May 04 12:50:05 2010 +0100
@@ -151,9 +151,7 @@
 instVarAt:index
     "redefined to suppress direct access to my address, which is a non-object"
 
-    index == 1 ifTrue:[
-        ^ self address
-    ].
+    index == 1 ifTrue:[^ self address].
     ^ super instVarAt:index
 
     "Created: / 3.9.1999 / 13:47:03 / ps"
@@ -306,13 +304,14 @@
 !ExternalAddress class methodsFor:'documentation'!
 
 version
-    ^ '$Id: ExternalAddress.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ExternalAddress.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/ExternalAddress.st,v 1.24 2009/12/07 15:58:16 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/ExternalAddress.st,v 1.25 2010/04/08 11:57:19 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: ExternalAddress.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ExternalAddress.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
+
--- a/ExternalBytes.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/ExternalBytes.st	Tue May 04 12:50:05 2010 +0100
@@ -746,9 +746,7 @@
 instVarAt:index
     "redefined to suppress direct access to my address, which is a non-object"
 
-    index == 1 ifTrue:[
-	^ self address
-    ].
+    index == 1 ifTrue:[^ self address].
     ^ super instVarAt:index
 ! !
 
@@ -1281,15 +1279,16 @@
 !ExternalBytes class methodsFor:'documentation'!
 
 version
-    ^ '$Id: ExternalBytes.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ExternalBytes.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/ExternalBytes.st,v 1.77 2010/03/12 14:35:17 stefan Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/ExternalBytes.st,v 1.78 2010/04/08 11:57:17 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: ExternalBytes.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ExternalBytes.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 ExternalBytes initialize!
+
--- a/ExternalStream.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/ExternalStream.st	Tue May 04 12:50:05 2010 +0100
@@ -2522,7 +2522,7 @@
 
     |line|
 
-%{  /* STACK:34000 */
+%{  /* STACK:100000 */
 
     FILEPOINTER f;
     int len, ret;
@@ -2539,123 +2539,123 @@
      || (__INST(handleType) == @symbol(filePointer))
      || (__INST(handleType) == @symbol(socketFilePointer))
      || (__INST(handleType) == @symbol(pipeFilePointer))) {
-	if (((fp = __INST(handle)) != nil)
-	    && (__INST(mode) != @symbol(writeonly))
-	    && (__INST(binary) != true)
-	) {
-	    f = __FILEVal(fp);
-	    buffer[0] = '\0';
-
-	    _buffered = (__INST(buffered) == true);
-	    if (_buffered) {
-		__READING__(f);
-	    }
-
-	    rslt = nextPtr = buffer;
-	    limit = buffer + sizeof(buffer) - 2;
-
-	    for (;;) {
-		__READBYTE__(ret, f, nextPtr, _buffered, __INST(handleType));
-		if (ret <= 0) {
-		    if (nextPtr == buffer)
-			rslt = NULL;
-		    if (ret == 0) {
-			__INST(hitEOF) = true;
-			break;
-		    } else {
-			__INST(lastErrorNumber) = __mkSmallInteger(__threadErrno);
-			goto err;
-		    }
-		}
-
-		if (*nextPtr == '\n') {
-		    cutOff = 1;
-		    *nextPtr = '\0';
-		    break;
-		}
-		if (*nextPtr == '\r') {
-		    char peekChar;
-
-		    /*
-		     * peek ahead for a newLine ...
-		     */
-		    __READBYTE__(ret, f, &peekChar, _buffered, __INST(handleType));
-		    if (ret <= 0) {
-			cutOff = 1;
-			*nextPtr = '\0';
-			if (ret == 0) {
-			    __INST(hitEOF) = true;
-			    break;
-			}
-			__INST(lastErrorNumber) = __mkSmallInteger(__threadErrno);
-			goto err;
-		    }
-
-		    if (peekChar == '\n') {
-			cutOff = 2;
-			*nextPtr = '\0';
-			break;
-		    }
-
-		    __UNGETC__(peekChar, f, _buffered);
-
-		    cutOff = 1;
-		    *nextPtr = '\0';
-		    break;
-		}
-
-		nextPtr++;
-		if (nextPtr >= limit) {
-		    *nextPtr = '\0';
-		    lineTooLong = 1;
-		    if (@global(InfoPrinting) == true) {
-			fprintf(stderr, "ExtStream [warning]: line truncated in nextLine\n");
-		    }
-		    break;
-		}
-	    }
-
-	    if (rslt != NULL) {
-		len = nextPtr-buffer;
-
-		if (__isSmallInteger(__INST(position))) {
-		    INT np = __intVal(__INST(position)) + len + cutOff;
-		    OBJ t;
-
-		    t = __MKINT(np); __INST(position) = t; __STORE(self, t);
-		} else {
-		    __INST(position) = nil; /* i.e. do not know */
-		}
-		/* remove any EOL character */
-		if (len != 0) {
-		    if (buffer[len-1] == '\n') {
-			buffer[--len] = '\0';
-		    }
-		    if ((len != 0) && (buffer[len-1] == '\r')) {
-			buffer[--len] = '\0';
-		    }
-		}
-		line = __MKSTRING_L(buffer, len);
-		if (! lineTooLong) {
-		    RETURN ( line );
-		}
-	    }
-	}
+        if (((fp = __INST(handle)) != nil)
+            && (__INST(mode) != @symbol(writeonly))
+            && (__INST(binary) != true)
+        ) {
+            f = __FILEVal(fp);
+            buffer[0] = '\0';
+
+            _buffered = (__INST(buffered) == true);
+            if (_buffered) {
+                __READING__(f);
+            }
+
+            rslt = nextPtr = buffer;
+            limit = buffer + sizeof(buffer) - 2;
+
+            for (;;) {
+                __READBYTE__(ret, f, nextPtr, _buffered, __INST(handleType));
+                if (ret <= 0) {
+                    if (nextPtr == buffer)
+                        rslt = NULL;
+                    if (ret == 0) {
+                        __INST(hitEOF) = true;
+                        break;
+                    } else {
+                        __INST(lastErrorNumber) = __mkSmallInteger(__threadErrno);
+                        goto err;
+                    }
+                }
+
+                if (*nextPtr == '\n') {
+                    cutOff = 1;
+                    *nextPtr = '\0';
+                    break;
+                }
+                if (*nextPtr == '\r') {
+                    char peekChar;
+
+                    /*
+                     * peek ahead for a newLine ...
+                     */
+                    __READBYTE__(ret, f, &peekChar, _buffered, __INST(handleType));
+                    if (ret <= 0) {
+                        cutOff = 1;
+                        *nextPtr = '\0';
+                        if (ret == 0) {
+                            __INST(hitEOF) = true;
+                            break;
+                        }
+                        __INST(lastErrorNumber) = __mkSmallInteger(__threadErrno);
+                        goto err;
+                    }
+
+                    if (peekChar == '\n') {
+                        cutOff = 2;
+                        *nextPtr = '\0';
+                        break;
+                    }
+
+                    __UNGETC__(peekChar, f, _buffered);
+
+                    cutOff = 1;
+                    *nextPtr = '\0';
+                    break;
+                }
+
+                nextPtr++;
+                if (nextPtr >= limit) {
+                    *nextPtr = '\0';
+                    lineTooLong = 1;
+                    if (@global(InfoPrinting) == true) {
+                        fprintf(stderr, "ExtStream [warning]: line truncated in nextLine\n");
+                    }
+                    break;
+                }
+            }
+
+            if (rslt != NULL) {
+                len = nextPtr-buffer;
+
+                if (__isSmallInteger(__INST(position))) {
+                    INT np = __intVal(__INST(position)) + len + cutOff;
+                    OBJ t;
+
+                    t = __MKINT(np); __INST(position) = t; __STORE(self, t);
+                } else {
+                    __INST(position) = nil; /* i.e. do not know */
+                }
+                /* remove any EOL character */
+                if (len != 0) {
+                    if (buffer[len-1] == '\n') {
+                        buffer[--len] = '\0';
+                    }
+                    if ((len != 0) && (buffer[len-1] == '\r')) {
+                        buffer[--len] = '\0';
+                    }
+                }
+                line = __MKSTRING_L(buffer, len);
+                if (! lineTooLong) {
+                    RETURN ( line );
+                }
+            }
+        }
     }
 err: ;
 %}.
     line notNil ifTrue:[
-	"/ the line as read is longer than 32k characters (boy - what a line)
-	"/ The exception could be handled by reading more and returning the
-	"/ concatenation in your exception handler (the receiver and the partial
-	"/ line are passed as parameter)
-
-	LineTooLongErrorSignal isHandled ifTrue:[
-	    ^ LineTooLongErrorSignal
-		raiseRequestWith:(Array with:self with:line)
-		     errorString:('line too long read error')
-	].
-	^ line , self nextLine
+        "/ the line as read is longer than 32k characters (boy - what a line)
+        "/ The exception could be handled by reading more and returning the
+        "/ concatenation in your exception handler (the receiver and the partial
+        "/ line are passed as parameter)
+
+        LineTooLongErrorSignal isHandled ifTrue:[
+            ^ LineTooLongErrorSignal
+                raiseRequestWith:(Array with:self with:line)
+                     errorString:('line too long read error')
+        ].
+        ^ line , self nextLine
     ].
 
     (hitEOF == true) ifTrue:[^ self pastEndRead].
@@ -5691,15 +5691,16 @@
 !ExternalStream class methodsFor:'documentation'!
 
 version
-    ^ '$Id: ExternalStream.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ExternalStream.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/ExternalStream.st,v 1.340 2010/02/09 14:23:16 stefan Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/ExternalStream.st,v 1.341 2010/04/12 19:27:17 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: ExternalStream.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: ExternalStream.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 ExternalStream initialize!
+
--- a/Filename.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/Filename.st	Tue May 04 12:50:05 2010 +0100
@@ -4113,7 +4113,7 @@
      'smalltalk.rc' asFilename mimeTypeFromName     
      'bitmaps/SBrowser.xbm' asFilename mimeTypeFromName    
      '../../rules/stmkmf' asFilename mimeTypeFromName  
-     '/bläh' asFilename mimeTypeFromName               
+     '/blh' asFilename mimeTypeFromName               
      '/x.zip' asFilename mimeTypeFromName               
      '/x.gz' asFilename mimeTypeFromName               
     "
@@ -4232,7 +4232,7 @@
      'smalltalk.rc' asFilename mimeTypeOfContents      
      'bitmaps/SBrowser.xbm' asFilename mimeTypeOfContents    
      '../../rules/stmkmf' asFilename mimeTypeOfContents 
-     '/bläh' asFilename mimeTypeOfContents              
+     '/blh' asFilename mimeTypeOfContents              
      'C:\Dokumente und Einstellungen\cg\Favoriten\languages.lnk' asFilename mimeTypeOfContents
      'G:\A\A01.TOP' asFilename mimeTypeOfContents       
     "
@@ -5074,19 +5074,25 @@
         this returns the file-names as strings; 
         see also #directoryContentsAsFilenames, which returns fileName instances."
 
-    |s contents|
-
-    s := DirectoryStream directoryNamed:(self osNameForDirectoryContents).
-    s isNil ifTrue:[^nil].
-
-    [ 
-        contents := s contents.
+    |directoryStream contents|
+
+    contents := OrderedCollection new.
+    directoryStream := DirectoryStream directoryNamed:(self osNameForDirectoryContents).
+    directoryStream isNil ifTrue:[^ nil].
+
+    [
+        [directoryStream atEnd] whileFalse:[  
+            |entry|
+
+            entry := directoryStream nextLine.
+            (entry notNil and:[entry ~= '.' and:[entry ~= '..']]) ifTrue:[
+                contents add:entry
+            ].
+        ].
     ] ensure:[
-        s close
+        directoryStream close
     ].
 
-    contents remove:'.' ifAbsent:nil.
-    contents remove:'..' ifAbsent:nil.
     ^ contents.
 
     "
@@ -5112,7 +5118,7 @@
 
     names := self directoryContents.
     names isNil ifTrue:[^ nil].
-    ^ names asOrderedCollection collect:[:entry | self construct:entry].
+    ^ names collect:[:entry | self construct:entry].
 
     "
      '.' asFilename directoryContentsAsFilenames   
@@ -5130,22 +5136,14 @@
 
     |files|
 
+    "here we get the files without '.' and '..'"
     files := self directoryContents.
     files isNil ifTrue:[
         "/ mhmh - that one does not exist
         ^ files
     ].
 
-    "/ add/remove parentDirectory if there is one/none
-
-    files remove:'.' ifAbsent:nil.
-    self isRootDirectory ifTrue:[
-        files remove:'..' ifAbsent:nil.
-    ] ifFalse:[
-        (files includes:'..') ifFalse:[
-            files addFirst:'..'.
-        ]
-    ].
+    files addFirst:'..'.
     ^ files
 
     "
@@ -5212,7 +5210,7 @@
 
     names := self recursiveDirectoryContents.
     names isNil ifTrue:[^ nil].
-    ^ names asOrderedCollection collect:[:entry | self construct:entry].
+    ^ names collect:[:entry | self construct:entry].
 
     "
      '.' asFilename recursiveDirectoryContentsAsFilenames   
@@ -5777,15 +5775,16 @@
 !Filename class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Filename.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: Filename.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/Filename.st,v 1.349 2009/12/14 14:20:41 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/Filename.st,v 1.350 2010/04/30 16:49:05 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: Filename.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: Filename.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 Filename initialize!
+
--- a/Integer.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/Integer.st	Tue May 04 12:50:05 2010 +0100
@@ -1654,19 +1654,6 @@
      "
 !
 
-bitInvert32
-    "return a new integer, where the low32 bits are complemented."
-
-    ^ self bitXor: 16rFFFFFFFF
-
-    "
-     16r80000000 bitInvert32 hexPrintString
-     16r7FFFFFFF bitInvert32 hexPrintString
-     16rFFFFFFFF bitInvert32 hexPrintString
-     0 bitInvert32 hexPrintString
-    "
-!
-
 bitOr:anInteger
     "return the bitwise-or of the receiver and the argument, anInteger.
      This is a general and slow implementation, walking over the bytes of
@@ -2883,7 +2870,7 @@
     ^ fibUsingDict value:self
 
     "the running time is mostly dictated by the LargeInteger multiplication performance...
-     (therefore, we get O² execution times, even for a linear number of multiplications)
+     (therefore, we get O execution times, even for a linear number of multiplications)
 
      Time millisecondsToRun:[50000 fib_iterative]  312    (DUO 1.7Ghz CPU)
      Time millisecondsToRun:[50000 fib_helper]     109
@@ -3933,6 +3920,7 @@
     "Modified: 15.10.1997 / 18:43:49 / cg"
 ! !
 
+
 !Integer methodsFor:'special access'!
 
 exponent
@@ -4711,15 +4699,16 @@
 !Integer class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Integer.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: Integer.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/Integer.st,v 1.245 2010/03/12 11:33:00 stefan Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/Integer.st,v 1.246 2010/04/13 16:11:42 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Integer.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: Integer.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 Integer initialize!
+
--- a/LargeInteger.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/LargeInteger.st	Tue May 04 12:50:05 2010 +0100
@@ -1290,6 +1290,133 @@
     "
 ! !
 
+!LargeInteger methodsFor:'bit operators-32bit'!
+
+bitInvert32
+    "return the value of the receiver with all bits inverted in 32bit signed int space
+     (changes the sign)"
+
+%{  /* NOCONTEXT */
+    unsigned INT v;
+
+    v = __unsignedLongIntVal(self);
+    v = ~v;
+#if __POINTER_SIZE__ == 8
+    v &= 0xFFFFFFFFL;
+#endif
+    RETURN ( __MKUINT(v) );
+%}.
+    ^ self primitiveFailed
+
+    "
+     16r80000000 bitInvert32 hexPrintString
+     16r7FFFFFFF bitInvert32 hexPrintString
+     16rFFFFFFFF bitInvert32 hexPrintString
+     0 bitInvert32 hexPrintString
+    "
+!
+
+bitRotate32:shiftCount
+    "return the value of the receiver rotated by shiftCount bits,
+     but only within 32 bits, rotating left for positive, right for negative counts.
+     Rotates through the sign bit.
+     Useful for crypt algorithms, or to emulate C/Java semantics."
+
+%{  /* NOCONTEXT */
+
+    unsigned INT bits;
+    int count;
+
+    if (__isSmallInteger(shiftCount)) {
+        count = __intVal(shiftCount);
+        count = count % 32;
+
+        bits = __unsignedLongIntVal(self);
+        if (count > 0) {
+            bits = (bits << count) | (bits >> (32-count));
+        } else {
+            bits = (bits >> (-count)) | (bits << (32-(-count)));
+        }
+#if __POINTER_SIZE__ == 8
+        bits &= 0xFFFFFFFFL;
+#endif
+        RETURN (__MKUINT(bits));
+    }
+%}.
+    ^ self primitiveFailed
+
+    "
+     (1 bitShift32:31) rotate32:0   
+     (1 bitShift32:31) rotate32:1   
+     (1 bitShift32:31) rotate32:-1   
+    "
+!
+
+bitShift32:shiftCount
+    "return the value of the receiver shifted by shiftCount bits,
+     but only within 32 bits, shifting into/out-of the sign bit.
+     May be useful for communication interfaces, to create ST-numbers
+     from a signed 32bit int value given as individual bytes,
+     or to emulate C/Java semantics.
+     The shift is unsigned"
+
+%{  /* NOCONTEXT */
+
+    unsigned INT bits;
+    int count;
+
+    if (__isSmallInteger(shiftCount)) {
+        count = __intVal(shiftCount);
+        if (count >= 32) {
+            RETURN (__mkSmallInteger(0));
+        }
+
+        bits = __unsignedLongIntVal(self);
+        if (count > 0) {
+            bits = bits << count;
+        } else {
+            bits = bits >> (-count);
+        }
+#if __POINTER_SIZE__ == 8
+        bits &= 0xFFFFFFFFL;
+#endif
+        RETURN (__MKUINT(bits));
+    }
+%}.
+    ^ self primitiveFailed
+
+    "
+     128 bitShift:24
+     128 bitShift32:24
+
+     1 bitShift:31
+     1 bitShift32:31
+    "
+!
+
+bitXor32:aNumber
+    "return the xor of the receiver and the argument.
+     The argument must be a SmallInteger or a 4-byte LargeInteger.
+     If the result overflows the 32 bit range, the value modulo 16rFFFFFFFF is returned.
+     This is of course not always correct, but allows for C/Java behavior to be emulated."
+
+%{  /* NOCONTEXT */
+    INT rslt;
+
+    rslt =  __unsignedLongIntVal(self) ^ __unsignedLongIntVal(aNumber);
+#if __POINTER_SIZE__ == 8
+    rslt &= 0xFFFFFFFFL;
+#endif
+    RETURN ( __MKUINT(rslt));
+%}.
+    self primitiveFailed
+
+    "
+     16r7FFFFFFF bitXor: 16r80000000          4294967295
+     16r7FFFFFFF bitXor32: 16r80000000
+    "
+! !
+
 !LargeInteger methodsFor:'byte access'!
 
 digitAt:index
@@ -1397,6 +1524,25 @@
     ^ self
 !
 
+asSigned32
+    "return a 32-bit integer with my bit-pattern. Receiver must be unsigned (i.e. positive).
+     May be required for bit operations on the sign-bit and/or to
+     convert C/Java numbers."
+
+%{  /* NOCONTEXT */
+    int rslt;
+
+    rslt =  (int)(__unsignedLongIntVal(self));
+    RETURN ( __MKINT(rslt));
+%}.
+    self primitiveFailed
+
+    "
+     16r80000000 asSigned32
+     16r40000000 asSigned32
+    "
+!
+
 asSmallInteger
     "return a SmallInteger with same value as myself -
      the result is invalid if the receivers value cannot
@@ -1417,6 +1563,25 @@
     ^ value
 !
 
+asUnsigned32
+    "return a 32-bit integer with my bit-pattern. Receiver must be unsigned (i.e. positive).
+     May be required for bit operations on the sign-bit and/or to
+     convert C/Java numbers."
+
+%{  /* NOCONTEXT */
+    unsigned int rslt;
+
+    rslt =  (int)(__unsignedLongIntVal(self));
+    RETURN ( __MKUINT(rslt));
+%}.
+    self primitiveFailed
+
+    "
+     16r80000000 asUnsigned32
+     16r40000000 asUnsigned32
+    "
+!
+
 coerce:aNumber
     "convert the argument aNumber into an instance of the receivers class and return it."
 
@@ -2289,6 +2454,31 @@
     "Modified: / 9.1.1998 / 13:27:37 / cg"
 ! !
 
+!LargeInteger methodsFor:'modulu arithmetic'!
+
+plus32:aNumber
+    "return the sum of the receiver and the argument, as SmallInteger.
+     The argument must be another SmallInteger.
+     If the result overflows the 32 bit range, the value modulo 16rFFFFFFFF is returned.
+     This is of course not always correct, but allows for C/Java behavior to be emulated."
+
+%{  /* NOCONTEXT */
+    INT sum;
+
+    sum =  __unsignedLongIntVal(self) + __unsignedLongIntVal(aNumber);
+#if __POINTER_SIZE__ == 8
+    sum &= 0xFFFFFFFFL;
+#endif
+    RETURN ( __MKUINT(sum));
+%}.
+    self primitiveFailed
+
+    "
+     16r7FFFFFFF + 1       ->  2147483648
+     16r7FFFFFFF plus32: 1 ->  -2147483648  
+    "
+! !
+
 !LargeInteger methodsFor:'printing & storing'!
 
 xxxstoreOn:aStream
@@ -2369,9 +2559,8 @@
      otherDigitByteArray |
 
 %{  /* NOCONTEXT */
-    OBJ _digitByteArray = __INST(digitByteArray);
-
     if (__isLargeInteger(aLargeInteger)) {
+    	OBJ _digitByteArray = __INST(digitByteArray);
 	OBJ _otherDigitByteArray = __LargeIntegerInstPtr(aLargeInteger)->l_digits;
 
 	if (__isByteArray(_digitByteArray)
@@ -2385,16 +2574,16 @@
 	    if (_myLen == _otherLen) {
 tryAgain:
 		while (_myLen >= (sizeof(INT)*4)) {
-		    if ( (unsigned INT *)_myDigits[0] != (unsigned INT *)_otherDigits[0]) {
+		    if ( ((unsigned INT *)_myDigits)[0] != ((unsigned INT *)_otherDigits)[0]) {
 			RETURN(false);
 		    }
-		    if ( (unsigned INT *)_myDigits[1] != (unsigned INT *)_otherDigits[1]) {
+		    if ( ((unsigned INT *)_myDigits)[1] != ((unsigned INT *)_otherDigits)[1]) {
 			RETURN(false);
 		    }
-		    if ( (unsigned INT *)_myDigits[2] != (unsigned INT *)_otherDigits[2]) {
+		    if ( ((unsigned INT *)_myDigits)[2] != ((unsigned INT *)_otherDigits)[2]) {
 			RETURN(false);
 		    }
-		    if ( (unsigned INT *)_myDigits[3] != (unsigned INT *)_otherDigits[3]) {
+		    if ( ((unsigned INT *)_myDigits)[3] != ((unsigned INT *)_otherDigits)[3]) {
 			RETURN(false);
 		    }
 		    _myDigits += sizeof(INT)*4;
@@ -4950,13 +5139,14 @@
 !LargeInteger class methodsFor:'documentation'!
 
 version
-    ^ '$Id: LargeInteger.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: LargeInteger.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/LargeInteger.st,v 1.199 2010/02/26 20:20:38 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/LargeInteger.st,v 1.201 2010/04/14 08:00:14 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: LargeInteger.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: LargeInteger.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
+
--- a/Make.proto	Thu Apr 29 16:55:35 2010 +0100
+++ b/Make.proto	Tue May 04 12:50:05 2010 +0100
@@ -130,6 +130,7 @@
 $(OUTDIR)MiniInspector.$(O) MiniInspector.$(H): MiniInspector.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)NameSpace.$(O) NameSpace.$(H): NameSpace.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)OSErrorHolder.$(O) OSErrorHolder.$(H): OSErrorHolder.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)OSProcess.$(O) OSProcess.$(H): OSProcess.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ObjectMemory.$(O) ObjectMemory.$(H): ObjectMemory.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PackageId.$(O) PackageId.$(H): PackageId.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PluginSupport.$(O) PluginSupport.$(H): PluginSupport.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
@@ -394,3 +395,4 @@
 
 # ENDMAKEDEPEND --- do not remove this line
 
+
--- a/Make.spec	Thu Apr 29 16:55:35 2010 +0100
+++ b/Make.spec	Tue May 04 12:50:05 2010 +0100
@@ -1,4 +1,4 @@
-# $Header$
+# $Header: /cvs/stx/stx/libbasic/Make.spec,v 1.107 2010/04/27 08:10:27 stefan Exp $
 #
 # DO NOT EDIT 
 # automagically generated from the projectDefinition: stx_libbasic.
@@ -338,9 +338,9 @@
 	ImmutableArray \
 	ImmutableByteArray \
 	ImmutableString \
-	SandboxedMethod \
 	PrototypeLookupAlgorithm \
 	Lookup \
+	OSProcess \
 	BuiltinLookup \
 
 WIN32_CLASSES= \
@@ -646,9 +646,9 @@
     $(OUTDIR)ImmutableArray.$(O) \
     $(OUTDIR)ImmutableByteArray.$(O) \
     $(OUTDIR)ImmutableString.$(O) \
-    $(OUTDIR)SandboxedMethod.$(O) \
     $(OUTDIR)PrototypeLookupAlgorithm.$(O) \
     $(OUTDIR)Lookup.$(O) \
+    $(OUTDIR)OSProcess.$(O) \
     $(OUTDIR)BuiltinLookup.$(O) \
 
 WIN32_OBJS= \
@@ -664,3 +664,4 @@
 
 
 
+
--- a/Method.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/Method.st	Tue May 04 12:50:05 2010 +0100
@@ -2402,6 +2402,12 @@
     "
 !
 
+methodInvocationInfo
+    ^ nil
+
+    "Created: / 27-04-2010 / 13:36:12 / cg"
+!
+
 methodVarNames
     "return a collection with the methods local-variable names.
      Uses Parser to parse methods source and extract the names."
@@ -3085,15 +3091,16 @@
 !Method class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Method.st 10518 2010-04-29 15:55:35Z vranyj1 $'
+    ^ '$Id: Method.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ 'Header: /cvs/stx/stx/libbasic/Method.st,v 1.347 2010/04/07 17:36:33 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/Method.st,v 1.349 2010/04/27 12:27:33 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Method.st 10518 2010-04-29 15:55:35Z vranyj1 $'
+    ^ '$Id: Method.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 Method initialize!
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/OSProcess.st	Tue May 04 12:50:05 2010 +0100
@@ -0,0 +1,125 @@
+"{ Package: 'stx:libbasic' }"
+
+Object subclass:#OSProcess
+	instanceVariableNames:'pid parentPid commandLine'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'System-Support'
+!
+
+!OSProcess class methodsFor:'documentation'!
+
+documentation
+"
+    OSProcess is an abstract class. Instances represent operating system processes
+    (as opposed to Smalltalk processes).
+
+    [author:]
+        Stefan Vogel (stefan@zwerg)
+
+    [instance variables:]
+        pid         SmallInteger    the process id
+        parentPid   SmallInteger    the process id of the parent process
+        commandLine String          the command line of the running command.
+
+    [class variables:]
+
+    [see also:]
+        Process
+
+"
+! !
+
+!OSProcess methodsFor:'accessing'!
+
+commandLine
+    ^ commandLine
+!
+
+commandLine:something
+    commandLine := something.
+!
+
+parentPid
+    ^ parentPid
+!
+
+parentPid:something
+    parentPid := something.
+!
+
+pid
+    ^ pid
+!
+
+pid:something
+    pid := something.
+! !
+
+!OSProcess methodsFor:'queries'!
+
+getProcessHandle
+    "some OperatingSystems redefine this to resolve this to a processHandle
+     (which must be explicitely freed later).
+     Others simply return the pid here"
+
+    ^ self subclassResponsibility
+!
+
+isAlive
+    "answer true, if the process is still alive"
+
+    ^ self subclassResponsibility
+!
+
+isDead
+    "answer true, if the process is no longer alive"
+
+    ^ self isAlive not
+! !
+
+!OSProcess methodsFor:'terminating'!
+
+kill
+    "kill the process - the process does not get the chance to clean up"
+    
+    ^ self subclassResponsibility.
+!
+
+killGroup
+    "killl the processGroup - the processes does not get the chance to clean up"
+    
+    ^ self subclassResponsibility.
+!
+
+killWithAllChildren
+    "terminate gracefully the process with all of its child processes"
+
+    ^ self subclassResponsibility.
+!
+
+terminate
+    "terminate the process gracefully"
+
+    ^ self subclassResponsibility.
+!
+
+terminateGroup
+    "terminate the process group.
+     Under Windows, these is the same as terminateWithhAllChildren,
+     under unix, this terminates a subset of all children"
+
+   ^ self subclassResponsibility.
+!
+
+terminateWithAllChildren
+    "terminate gracefully the process with all of its child processes"
+
+    ^ self subclassResponsibility.
+! !
+
+!OSProcess class methodsFor:'documentation'!
+
+version_CVS
+    ^ '§Header: /cvs/stx/stx/libbasic/OSProcess.st,v 1.1 2010/04/27 08:07:00 stefan Exp §'
+! !
--- a/ProjectDefinition.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/ProjectDefinition.st	Tue May 04 12:50:05 2010 +0100
@@ -4464,6 +4464,7 @@
         self superclass: ApplicationDefinition.
         ^ self
     ].
+
     typeOrNil = NonGUIApplicationType ifTrue:[
         self compile:
 'isGUIApplication
@@ -4476,6 +4477,7 @@
         self superclass: ApplicationDefinition.
         ^ self
     ].                
+
     self theMetaclass removeSelector: #isGUIApplication.
     self superclass: LibraryDefinition.
     ^ self.
@@ -5376,18 +5378,19 @@
 !ProjectDefinition class methodsFor:'documentation'!
 
 version
-    ^ '$Id: ProjectDefinition.st 10513 2010-04-10 12:06:28Z vranyj1 $'
+    ^ '$Id: ProjectDefinition.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ 'Header: /cvs/stx/stx/libbasic/ProjectDefinition.st,v 1.311 2010/03/24 11:21:23 sr Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/ProjectDefinition.st,v 1.312 2010/04/07 17:51:24 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: ProjectDefinition.st 10513 2010-04-10 12:06:28Z vranyj1 $'
+    ^ '$Id: ProjectDefinition.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 ProjectDefinition initialize!
 
 
 
+
--- a/SHA1Stream.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/SHA1Stream.st	Tue May 04 12:50:05 2010 +0100
@@ -443,17 +443,26 @@
     "Test Vectors (from FIPS PUB 180-1)"
 
     ^ #(
-	('abc'
-	 #[16rA9 16r99 16r3E 16r36  16r47 16r06 16r81 16r6A  16rBA 16r3E 16r25 16r71
-	   16r78 16r50 16rC2 16r6C  16r9C 16rD0 16rD8 16r9D])
+        ('Franz jagt im komplett verwahrlosten Taxi quer durch Bayern'
+         '68ac906495480a3404beee4874ed853a037a7a8f')
+
+        ('Frank jagt im komplett verwahrlosten Taxi quer durch Bayern'
+         'd8e8ece39c437e515aa8997c1a1e94f1ed2a0e62')
+
+        (''
+         'da39a3ee5e6b4b0d3255bfef95601890afd80709')
 
-	('abcdbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq'
-	  #[16r84 16r98 16r3E 16r44  16r1C 16r3B 16rD2 16r6E  16rBA 16rAE 16r4A 16rA1
-	    16rF9 16r51 16r29 16rE5  16rE5 16r46 16r70 16rF1])
+        ('abc'
+         #[16rA9 16r99 16r3E 16r36  16r47 16r06 16r81 16r6A  16rBA 16r3E 16r25 16r71
+           16r78 16r50 16rC2 16r6C  16r9C 16rD0 16rD8 16r9D])
+
+        ('abcdbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq'
+          #[16r84 16r98 16r3E 16r44  16r1C 16r3B 16rD2 16r6E  16rBA 16rAE 16r4A 16rA1
+            16rF9 16r51 16r29 16rE5  16rE5 16r46 16r70 16rF1])
        ) copyWith:
-	(Array with:(String new:1000000 withAll:$a)
-	       with:#[16r34 16rAA 16r97 16r3C  16rD4 16rC4 16rDA 16rA4  16rF6 16r1E 16rEB 16r2B
-		      16rDB 16rAD 16r27 16r31  16r65 16r34 16r01 16r6F])
+        (Array with:(String new:1000000 withAll:$a)
+               with:#[16r34 16rAA 16r97 16r3C  16rD4 16rC4 16rDA 16rA4  16rF6 16r1E 16rEB 16r2B
+                      16rDB 16rAD 16r27 16r31  16r65 16r34 16r01 16r6F])
 
     "
      self test
@@ -673,15 +682,16 @@
 !SHA1Stream class methodsFor:'documentation'!
 
 version
-    ^ '$Id: SHA1Stream.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: SHA1Stream.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/SHA1Stream.st,v 1.18 2010/03/04 14:33:51 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/SHA1Stream.st,v 1.19 2010/04/13 14:36:36 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: SHA1Stream.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: SHA1Stream.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 SHA1Stream initialize!
+
--- a/SequenceableCollection.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/SequenceableCollection.st	Tue May 04 12:50:05 2010 +0100
@@ -7155,15 +7155,11 @@
      See also #quickSort and #randomizedSort for other sort algorithms
      with different worst- and average case behavior)"
 
-    |stop|
-
-    stop := self size.
-    (stop > 1) ifTrue:[
-	self mergeSort:[:a :b | a < b] from:1 to:stop
-    ]
+    self mergeSort:[:a :b | a < b]
 
     "
      #(1 16 7 98 3 19 4 0) mergeSort
+     #(1 16 7 98 7 3 19 4 0) mergeSort 
 
      |data|
      data := Random new next:100000.
@@ -7766,15 +7762,16 @@
 !SequenceableCollection class methodsFor:'documentation'!
 
 version
-    ^ '$Id: SequenceableCollection.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: SequenceableCollection.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/SequenceableCollection.st,v 1.294 2010/03/04 13:18:13 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/SequenceableCollection.st,v 1.295 2010/04/23 13:39:19 mb Exp §'
 !
 
 version_SVN
-    ^ '$Id: SequenceableCollection.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: SequenceableCollection.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 SequenceableCollection initialize!
+
--- a/SmallInteger.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/SmallInteger.st	Tue May 04 12:50:05 2010 +0100
@@ -1466,6 +1466,12 @@
 
 !SmallInteger methodsFor:'bit operators-32bit'!
 
+asSigned32
+    "return a 32-bit integer with my bit-pattern. For protocol completeness."
+
+    ^ self
+!
+
 asUnsigned32
     "return a 32-bit integer with my bit-pattern, but positive.
      May be required for bit operations on the sign-bit and/or to
@@ -1484,6 +1490,73 @@
     "
 !
 
+bitInvert32
+    "return the value of the receiver with all bits inverted in 32bit signed int space
+     (changes the sign)"
+
+%{  /* NOCONTEXT */
+    unsigned INT v;
+
+    v = __intVal(self);
+    v = ~v;
+#if __POINTER_SIZE__ == 8
+    v &= 0xFFFFFFFFL;
+#endif
+    RETURN ( __MKUINT(v) );
+%}.
+    ^ self primitiveFailed
+
+    "
+     1 bitInvert32
+     16r40000000 bitInvert32
+     16r80000000 bitInvert32
+    "
+!
+
+bitRotate32:shiftCount
+    "return the value of the receiver rotated by shiftCount bits,
+     but only within 32 bits, rotating left for positive, right for negative counts.
+     Rotates through the sign bit.
+     Useful for crypt algorithms, or to emulate C/Java semantics."
+
+%{  /* NOCONTEXT */
+
+    unsigned INT bits;
+    int count;
+
+    if (__isSmallInteger(shiftCount)) {
+        count = __intVal(shiftCount);
+        count = count % 32;
+
+        bits = __intVal(self);
+        if (count > 0) {
+            bits = (bits << count) | (bits >> (32-count));
+        } else {
+            bits = (bits >> (-count)) | (bits << (32-(-count)));
+        }
+#if __POINTER_SIZE__ == 8
+        bits &= 0xFFFFFFFFL;
+#endif
+        RETURN (__MKUINT(bits));
+    }
+%}.
+    ^ self primitiveFailed
+
+    "
+     128 rotate32:1
+
+     1 rotate32:1   
+     1 rotate32:2   
+     1 rotate32:31
+     1 rotate32:32
+
+     1 rotate32:-1   
+     1 rotate32:-2   
+     1 rotate32:-3   
+     1 rotate32:-32   
+    "
+!
+
 bitShift32:shiftCount
     "return the value of the receiver shifted by shiftCount bits,
      but only within 32 bits, shifting into/out-of the sign bit.
@@ -1524,6 +1597,29 @@
     "
 !
 
+bitXor32:aNumber
+    "return the xor of the receiver and the argument.
+     The argument must be another SmallInteger or a 4-byte LargeInteger.
+     If the result overflows the 32 bit range, the value modulo 16rFFFFFFFF is returned.
+     This is of course not always correct, but allows for C/Java behavior to be emulated."
+
+%{  /* NOCONTEXT */
+    INT rslt;
+
+    rslt =  __unsignedLongIntVal(self) ^ __unsignedLongIntVal(aNumber);
+#if __POINTER_SIZE__ == 8
+    rslt &= 0xFFFFFFFFL;
+#endif
+    RETURN ( __MKUINT(rslt));
+%}.
+    self primitiveFailed
+
+    "
+     16r7FFFFFFF bitXor: 16r80000000          4294967295
+     16r7FFFFFFF bitXor32: 16r80000000
+    "
+!
+
 unsignedBitShift32:shiftCount
     "return the value of the receiver shifted by shiftCount bits,
      but only within 32 unsigned bits.
@@ -1983,6 +2079,30 @@
     ^ 20
 !
 
+signExtended24BitValue
+    "return a smallInteger from sign-extending the 24'th bit.
+     May be useful for communication interfaces"
+
+%{  /* NOCONTEXT */
+    INT i = __intVal(self);
+
+    if (i & 0x800000) {
+        i = i | ~0xFFFFFFL;
+    } else {
+        i = i & 0x7FFFFF;
+    }
+
+    RETURN (__mkSmallInteger(i));
+%}.
+    ^ self primitiveFailed
+
+    "
+     16rFFFFFF signExtended24BitValue
+     16r800000 signExtended24BitValue
+     16r7FFFFF signExtended24BitValue
+    "
+!
+
 signExtendedByteValue
     "return a smallInteger from sign-extending the 8'th bit.
      May be useful for communication interfaces"
@@ -1991,9 +2111,9 @@
     INT i = __intVal(self);
 
     if (i & 0x80) {
-	i = i | ~0xFFL;
+        i = i | ~0xFFL;
     } else {
-	i = i & 0x7F;
+        i = i & 0x7F;
     }
 
     RETURN (__mkSmallInteger(i));
@@ -2001,8 +2121,9 @@
     ^ self primitiveFailed
 
     "
-     16rFF signExtendedByteValue
-     16r7F signExtendedByteValue
+     16rFF signExtendedByteValue 
+     16r80 signExtendedByteValue 
+     16r7F signExtendedByteValue 
     "
 !
 
@@ -2014,9 +2135,9 @@
     INT i = __intVal(self);
 
     if (i & 0x8000) {
-	i = i | ~0xFFFFL;
+        i = i | ~0xFFFFL;
     } else {
-	i = i & 0x7FFF;
+        i = i & 0x7FFF;
     }
 
     RETURN (__mkSmallInteger(i));
@@ -2024,8 +2145,9 @@
     ^ self primitiveFailed
 
     "
-     16rFFFF signExtendedShortValue
-     16r7FFF signExtendedShortValue
+     16rFFFF signExtendedShortValue 
+     16r8000 signExtendedShortValue 
+     16r7FFF signExtendedShortValue 
     "
 ! !
 
@@ -3128,6 +3250,29 @@
 
 !SmallInteger methodsFor:'modulo arithmetic'!
 
+plus32:aNumber
+    "return the sum of the receiver and the argument, as SmallInteger.
+     The argument must be another SmallInteger.
+     If the result overflows the 32 bit range, the value modulo 16rFFFFFFFF is returned.
+     This is of course not always correct, but allows for C/Java behavior to be emulated."
+
+%{  /* NOCONTEXT */
+    INT sum;
+
+    sum =  __unsignedLongIntVal(self) + __unsignedLongIntVal(aNumber);
+#if __POINTER_SIZE__ == 8
+    sum &= 0xFFFFFFFFL;
+#endif
+    RETURN ( __MKUINT(sum));
+%}.
+    self primitiveFailed
+
+    "
+     16r7FFFFFFF + 1          2147483648
+     16r7FFFFFFF plus32: 1    
+    "
+!
+
 plus:aNumber
     "return the sum of the receiver and the argument, as SmallInteger.
      The argument must be another SmallInteger.
@@ -3772,13 +3917,14 @@
 !SmallInteger class methodsFor:'documentation'!
 
 version
-    ^ '$Id: SmallInteger.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: SmallInteger.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/SmallInteger.st,v 1.183 2010/03/12 14:12:29 stefan Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/SmallInteger.st,v 1.185 2010/04/13 18:58:23 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: SmallInteger.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: SmallInteger.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
+
--- a/Smalltalk.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/Smalltalk.st	Tue May 04 12:50:05 2010 +0100
@@ -566,7 +566,7 @@
 
     |idx|
 
-    NumberOfClassesHint := 4500.
+    NumberOfClassesHint := 10000.
 
     Initializing := true.
 
@@ -1713,7 +1713,7 @@
 
     |already|
 
-    already := IdentitySet new:NumberOfClassesHint*3.
+    already := IdentitySet new:NumberOfClassesHint*2.
     self allClassesDo:[:eachClass | 
         |cls|
 
@@ -3870,7 +3870,7 @@
      but in addition put the message into the splash screen (if there is one).
      Use this for info messages during startup"
 
-    aString infoPrintCR.
+    aString notNil ifTrue:[ aString infoPrintCR ].
     self showSplashMessage:aString color:nil.
 !
 
@@ -4822,9 +4822,7 @@
         ].
     ].
 
-    ((dir / 'loadAll') exists
-    or:[(dir / 'abbrev.stc') exists
-    ]) ifTrue:[
+    ((dir / 'loadAll') exists or:[(dir / 'abbrev.stc') exists]) ifTrue:[
         KnownPackages isNil ifTrue:[
             KnownPackages := Set new.
         ].
@@ -4850,47 +4848,46 @@
     ].
 
     [
-        directoryContents := dir directoryContents.
+        directoryContents := dir directoryContents asSet.   "asSet to speed up remove"
     ] on:FileStream openErrorSignal do:[:ex|
         "non-accessable directory: we are done"
         ^ self
     ].
 
-    directoryContents do:[:aFilename |
+    directoryContents removeAllFoundIn:#(
+                            'objbc'
+                            'objvc'
+                            'doc'
+                            'CVS'
+                            'bitmaps'
+                            'resources'
+                            'source'
+                            'not_delivered'
+                            'not_ported'
+                        ).
+    dir baseName = 'stx' ifTrue:[
+        directoryContents removeAllFoundIn:#(
+                            'configurations'
+                            'include'
+                            'rules'
+                            'stc'
+                            'support'
+                        ).
+    ].
+
+    directoryContents do:[:eachFilenameString |
         |f|
 
-        (#(
-            'objbc'
-            'doc'
-            'CVS'
-            'bitmaps'
-            'resources'
-            'source'
-            'not_delivered'
-            'not_ported'
-        ) includes:aFilename) ifFalse:[
-            ((dir baseName ~= 'stx')
-            or:[
-                (#(
-                    'configurations'
-                    'include'
-                    'rules'
-                    'stc'
-                    'support'
-                ) includes:aFilename) not])
-            ifTrue:[
-                f := dir / aFilename.
-                f isDirectory ifTrue:[
-                     self
-                        recursiveInstallAutoloadedClassesFrom:f
-                        rememberIn:dirsConsulted
-                        maxLevels:maxLevels-1
-                        noAutoload:noAutoloadHere
-                        packageTop:packageTopPath
-                        showSplashInLevels:showSplashInLevels - 1.
-                ]
-            ]
-        ].
+        f := dir / eachFilenameString.
+        f isDirectory ifTrue:[
+             self
+                recursiveInstallAutoloadedClassesFrom:f
+                rememberIn:dirsConsulted
+                maxLevels:maxLevels-1
+                noAutoload:noAutoloadHere
+                packageTop:packageTopPath
+                showSplashInLevels:showSplashInLevels - 1.
+        ]
     ].
 
     showSplashInLevels >= 0 ifTrue:[
@@ -7290,7 +7287,7 @@
      ST/X revision Naming is:
         <major>.<minor>.<revision>.<release>"
 
-    ^ 5
+    ^ 6
 
     "
      Smalltalk majorVersionNr
@@ -7310,7 +7307,7 @@
      ST/X revision Naming is:
         <major>.<minor>.<revision>.<release>"
 
-    ^ 4
+    ^ 1
 
     "
      Smalltalk minorVersionNr
@@ -7347,10 +7344,11 @@
      ST/X revision Naming is:
         <major>.<minor>.<revision>.<release>"
 
-    ^ 2
+    ^ 1
 
     "
      Smalltalk releaseNr
+     Smalltalk versionString
     "
 
     "Created: / 10-12-1995 / 01:42:19 / cg"
@@ -7368,7 +7366,7 @@
      ST/X revision Naming is:
         <major>.<minor>.<revision>.<release>"
 
-    ^ 6
+    ^ 1
 
     "
      Smalltalk revisionNr
@@ -7460,15 +7458,15 @@
 !Smalltalk class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Smalltalk.st 10513 2010-04-10 12:06:28Z vranyj1 $'
+    ^ '$Id: Smalltalk.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ 'Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.931 2010/03/26 12:05:10 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.935 2010/04/30 16:51:56 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: Smalltalk.st 10513 2010-04-10 12:06:28Z vranyj1 $'
+    ^ '$Id: Smalltalk.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 
@@ -7476,3 +7474,4 @@
 
 
 
+
--- a/SystemChangeNotifier.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/SystemChangeNotifier.st	Tue May 04 12:50:05 2010 +0100
@@ -42,7 +42,7 @@
 "
 ! !
 
-!SystemChangeNotifier class methodsFor:'instance creaton'!
+!SystemChangeNotifier class methodsFor:'instance creation'!
 
 uniqueInstance
     "I am a singleton"
@@ -113,9 +113,10 @@
 !SystemChangeNotifier class methodsFor:'documentation'!
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/SystemChangeNotifier.st,v 1.3 2009/10/26 17:31:00 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/SystemChangeNotifier.st,v 1.4 2010/04/14 16:13:57 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: SystemChangeNotifier.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: SystemChangeNotifier.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
+
--- a/UnixOperatingSystem.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/UnixOperatingSystem.st	Tue May 04 12:50:05 2010 +0100
@@ -5040,7 +5040,7 @@
 
     |path|
 
-%{  /* STACK: 16000 */
+%{  /* UNLIMITEDSTACK */
 
     if (__isStringLike(pathName)) {
 
@@ -6401,7 +6401,7 @@
     /*
      * allcate an array for keys and values
      */
-    resultArray = __MKARRAY(nEnv * 2);
+    resultArray = __ARRAY_NEW_INT(nEnv * 2);
     if (resultArray == nil) {
 	error = @symbol(allocationFailure);
 	goto bad;
@@ -6823,8 +6823,8 @@
 
     n_ifs = ifc.ifc_len / sizeof (struct ifreq);
 
-    nameArray    = __MKARRAY(n_ifs);
-    addressArray = __MKARRAY(n_ifs);
+    nameArray    = __ARRAY_NEW_INT(n_ifs);
+    addressArray = __ARRAY_NEW_INT(n_ifs);
 
     if (nameArray == nil || addressArray == nil) {
 	/* Creating a string wouldn/t work here */
@@ -6930,8 +6930,8 @@
 
     n_ifs = ifc.ifc_len / sizeof (struct ifreq);
 
-    nameArray    = __MKARRAY(n_ifs);
-    addressArray = __MKARRAY(n_ifs);
+    nameArray    = __ARRAY_NEW_INT(n_ifs);
+    addressArray = __ARRAY_NEW_INT(n_ifs);
 
     if (nameArray == nil || addressArray == nil) {
 	/* Creating a string wouldn/t work here */
@@ -9040,6 +9040,108 @@
     "
 !
 
+primUserInfoOf:aNameOrID
+    "return a dictionary filled with userinfo. The argument can be either
+     a string with the users name or its numeric id.
+     Notice, that not all systems provide (all of) this info;
+     DOS systems return nothing;
+     non-SYSV4 systems have no age/comment.
+     Portable applications may want to check the systemType and NOT depend
+     on all keys to be present in the returned dictionary.
+     Another notice: on some systems (SYSV4), the gecos field includes multiple
+     entries (i.e. not just the name), separated by commas. You may want to
+     extract any substring, up to the first comma to get the real life name."
+
+
+%{ /* UNLIMITEDSTACK */  /* Don't know whether NIS, LDAP or whatever is consulted */
+#if !defined(NO_PWD)
+    struct passwd *result = 0;
+    int ret;
+    int idx = 0;
+    OBJ returnArray;
+    OBJ tmp;
+
+#if defined(_POSIX_SOURCE)
+    char buf[4096];
+    struct passwd pwd;
+
+    if (__isStringLike(aNameOrID)) {
+        getpwnam_r(__stringVal(aNameOrID), &pwd, buf, sizeof(buf), &result);
+    } else if (__isSmallInteger(aNameOrID)) {
+        getpwuid_r(__intVal(aNameOrID), &pwd, buf, sizeof(buf), &result);
+    }
+#else
+    if (__isStringLike(aNameOrID)) {
+        result = getpwnam(__stringVal(aNameOrID));
+    } else if (__isSmallInteger(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);
+#  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);
+#  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);
+#  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);
+    }
+# endif /* ! NO_PWD */
+%}.
+    ^ nil
+
+    "
+     OperatingSystem primUserInfoOf:'root'
+     OperatingSystem primUserInfoOf:1
+     OperatingSystem primUserInfoOf:'cg'
+     OperatingSystem primUserInfoOf:'fooBar'
+     OperatingSystem primUserInfoOf:(OperatingSystem getUserID)
+    "
+!
+
 userInfoOf:aNameOrID
     "{ Pragma: +optSpace }"
 
@@ -9054,71 +9156,36 @@
      entries (i.e. not just the name), separated by commas. You may want to
      extract any substring, up to the first comma to get the real life name."
 
-    |info name passw uid gid age comment
-     gecos dir shell|
-
-%{
-# ifndef NO_PWD
-    struct passwd *buf;
-    int ret;
-
-    if (__isStringLike(aNameOrID)) {
-	buf = getpwnam(__stringVal(aNameOrID));
-    } else if (__isSmallInteger(aNameOrID)) {
-	buf = getpwuid(__intVal(aNameOrID));
-    } else {
-	buf = (struct passwd *)0;
-    }
-    if (buf) {
-	name = __MKSTRING(buf->pw_name);
-#  ifndef NO_PWD_PASSWD
-	passw = __MKSTRING(buf->pw_passwd);
-#  endif
-#  ifdef SYSV4
-	age = __MKSTRING(buf->pw_age);
-	comment = __MKSTRING(buf->pw_comment);
-#  endif
-	dir = __MKSTRING(buf->pw_dir);
-#  ifndef NO_PWD_GECOS
-	gecos = __MKSTRING(buf->pw_gecos);
-#  endif
-	shell = __MKSTRING(buf->pw_shell);
-
-	uid = __mkSmallInteger(buf->pw_uid);
-	gid = __mkSmallInteger(buf->pw_gid);
-    }
-# endif /* has PWD */
-%}.
+    |infoArray info name dir|
+
+    infoArray := self primUserInfoOf:aNameOrID.
     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].
+            ].
+        ].
+    ].
+
     name isNil ifTrue:[
-	aNameOrID == self getUserID ifTrue:[
-	    name := self getLoginName
-	].
-    ].
-    name notNil ifTrue:[
-	info at:#name put:name.
-    ] ifFalse:[
-	info at:#name put:'unknown'
-    ].
-    passw notNil ifTrue:[info at:#passwd put:passw].
-    age notNil ifTrue:[info at:#age put:age].
-    comment notNil ifTrue:[info at:#comment put:comment].
-    gecos notNil ifTrue:[info at:#gecos put:gecos].
-    shell notNil ifTrue:[info at:#shell put:shell].
+        info at:#name put:#unknown
+    ].
     dir isNil ifTrue:[
-	aNameOrID == self getUserID ifTrue:[
-	    dir := self getHomeDirectory
-	]
-    ].
-    dir notNil ifTrue:[info at:#dir put:dir].
-    uid notNil ifTrue:[info at:#uid put:uid].
-    gid  notNil ifTrue:[info at:#gid put:gid].
+        aNameOrID == self getUserID ifTrue:[
+            info at:#dir put:self getHomeDirectory
+        ]
+    ].
+
     ^ info
 
     "
      OperatingSystem userInfoOf:'root'
      OperatingSystem userInfoOf:1
-     OperatingSystem userInfoOf:'claus'
+     OperatingSystem userInfoOf:'cg'
      OperatingSystem userInfoOf:'fooBar'
      OperatingSystem userInfoOf:(OperatingSystem getUserID)
     "
@@ -11218,9 +11285,9 @@
     proto := self protocolCodeOf:protoArg.
     serviceNameArg notNil ifTrue:[
         serviceName := serviceNameArg printString.      "convert integer port numbers"
-    ]. "ifFalse:[serviveName := nil]"
-
-%{ /* STACK:32000 */
+    ].
+
+%{ /* STACK: 100000 */  /* Don't know whether DNS, NIS, LDAP or whatever is consulted */
 #undef xxAI_NUMERICHOST /* remove xx to test gethost...() path */
 
 
@@ -11541,15 +11608,18 @@
     1 to:result size do:[:i |
         |entry dom info|
 
+        entry := result at:i.
+
         info := SocketAddressInfo new.
-        entry := result at:i.
-        info flags:(entry at:1).
-        info domain:(dom := OperatingSystem domainSymbolOf:(entry at:2)).
-        info type:(OperatingSystem socketTypeSymbolOf:(entry at:3)).
-        info protocol:(self protocolSymbolOf:(entry at:4)).
-        info socketAddress:((SocketAddress newDomain:dom) fromBytes:(entry at:5)).
-        info canonicalName:(entry at:6).
-        result at:i put:info
+        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
 
@@ -11585,7 +11655,7 @@
 
     |error errorString hostName serviceName|
 
-%{  /* STACK:32000 */
+%{ /* STACK: 100000 */  /* Don't know whether DNS, NIS, LDAP or whatever is consulted */
 
 #undef xxNI_NUMERICHOST /* remove xx to test gethost...() path */
 
@@ -11605,20 +11675,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));
@@ -11626,187 +11696,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.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
     "
 ! !
 
@@ -12651,16 +12721,17 @@
 !UnixOperatingSystem class methodsFor:'documentation'!
 
 version
-    ^ '$Id: UnixOperatingSystem.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: UnixOperatingSystem.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/UnixOperatingSystem.st,v 1.268 2010/04/01 09:36:44 stefan Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/UnixOperatingSystem.st,v 1.274 2010/04/12 18:37:20 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: UnixOperatingSystem.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: UnixOperatingSystem.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 UnixOperatingSystem initialize!
 UnixOperatingSystem::FileDescriptorHandle initialize!
+
--- a/UserPreferences.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/UserPreferences.st	Tue May 04 12:50:05 2010 +0100
@@ -1489,6 +1489,71 @@
 
 !UserPreferences methodsFor:'accessing-prefs-browser-colors'!
 
+colorForInstrumentedFullyCoveredCode
+    "the color for code in the browser which is instrumented 
+     and where all branches have been executed (also code, which has been executed)"
+
+    |clr|
+
+    clr := self at:#colorForInstrumentedFullyCoveredCode ifAbsent:nil.
+    clr isNil ifTrue:[
+        clr := Color green slightlyDarkened.
+        self at:#colorForInstrumentedFullyCoveredCode put:clr.
+    ].
+    ^ clr
+
+    "
+     UserPreferences current
+        at:#emphasisForInstrumentedFullyCoveredCode 
+        put:(Color green slightlyDarkened).
+    "
+
+    "Created: / 28-04-2010 / 13:58:52 / cg"
+!
+
+colorForInstrumentedNeverCalledCode
+    "the color for code in the browser which is instrumented but has never been called"
+
+    |clr|
+
+    clr := self at:#colorForInstrumentedNeverCalledCode ifAbsent:nil.
+    clr isNil ifTrue:[
+        clr := Color red slightlyDarkened.
+        self at:#colorForInstrumentedNeverCalledCode put:clr.
+    ].
+    ^ clr
+
+    "
+     UserPreferences current
+        at:#colorForInstrumentedNeverCalledCode 
+        put:(Color red slightlyDarkened).
+    "
+
+    "Created: / 28-04-2010 / 13:59:43 / cg"
+!
+
+colorForInstrumentedPartiallyCoveredCode
+    "color for code in the browser which is instrumented and where some branches have been
+     executed"
+
+    |clr|
+
+    clr := self at:#colorForInstrumentedPartiallyCoveredCode ifAbsent:nil.
+    clr isNil ifTrue:[
+        clr := Color orange.
+        self at:#colorForInstrumentedPartiallyCoveredCode put:clr.
+    ].
+    ^ clr
+
+    "
+     UserPreferences current
+        at:#colorForInstrumentedPartiallyCoveredCode 
+        put:(Color orange slightlyLightened).
+    "
+
+    "Created: / 28-04-2010 / 14:00:56 / cg"
+!
+
 emphasisForChangedCode
     "the emphasis for changed code (in changeSet) in the browser"
 
@@ -1551,6 +1616,80 @@
     "
 !
 
+emphasisForInstrumentedFullyCoveredCode
+    "the emphasis for code in the browser which is instrumented and where all branches have been
+     executed"
+
+    |emp|
+
+    emp := self at:#emphasisForInstrumentedFullyCoveredCode ifAbsent:nil.
+    emp isNil ifTrue:[
+        emp := #color->Color green slightlyDarkened.
+        emp := Array with:#bold with:emp.
+        "/ emp := #color->Color blue darkened.
+        self at:#emphasisForInstrumentedFullyCoveredCode put:emp.
+    ].
+    ^ emp
+
+    "
+     UserPreferences current
+        at:#emphasisForInstrumentedFullyCoveredCode 
+        put:(Array with:#bold with:(#color->Color green slightlyDarkened)).
+    "
+
+    "Created: / 27-04-2010 / 13:01:01 / cg"
+    "Modified: / 27-04-2010 / 14:48:11 / cg"
+!
+
+emphasisForInstrumentedNeverCalledCode
+    "the emphasis for code in the browser which is instrumented but has never been called"
+
+    |emp|
+
+    emp := self at:#emphasisForInstrumentedNeverCalledCode ifAbsent:nil.
+    emp isNil ifTrue:[
+        emp := #color->Color red slightlyDarkened.
+        emp := Array with:#bold with:emp.
+        "/ emp := #color->Color blue darkened.
+        self at:#emphasisForInstrumentedNeverCalledCode put:emp.
+    ].
+    ^ emp
+
+    "
+     UserPreferences current
+        at:#emphasisForInstrumentedNeverCalledCode 
+        put:(Array with:#bold with:(#color->Color red slightlyDarkened)).
+    "
+
+    "Created: / 27-04-2010 / 12:59:47 / cg"
+    "Modified: / 27-04-2010 / 14:48:39 / cg"
+!
+
+emphasisForInstrumentedPartiallyCoveredCode
+    "the emphasis for code in the browser which is instrumented and where some branches have been
+     executed"
+
+    |emp|
+
+    emp := self at:#emphasisForInstrumentedPartiallyCoveredCode ifAbsent:nil.
+    emp isNil ifTrue:[
+        emp := #color->Color orange.
+        emp := Array with:#bold with:emp.
+        "/ emp := #color->Color blue darkened.
+        self at:#emphasisForInstrumentedPartiallyCoveredCode put:emp.
+    ].
+    ^ emp
+
+    "
+     UserPreferences current
+        at:#emphasisForInstrumentedPartiallyCoveredCode 
+        put:(Array with:#bold with:(#color->Color orange slightlyLightened)).
+    "
+
+    "Created: / 27-04-2010 / 13:01:20 / cg"
+    "Modified: / 27-04-2010 / 18:50:43 / cg"
+!
+
 emphasisForModifiedBuffer
     |emp|
 
@@ -3105,13 +3244,14 @@
 !UserPreferences class methodsFor:'documentation'!
 
 version
-    ^ '$Id: UserPreferences.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: UserPreferences.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.245 2010/03/15 11:49:20 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.248 2010/04/30 09:52:43 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: UserPreferences.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: UserPreferences.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
+
--- a/Win32OperatingSystem.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/Win32OperatingSystem.st	Tue May 04 12:50:05 2010 +0100
@@ -280,6 +280,11 @@
 #  include <windows.h>
 # endif
 
+# ifndef TLHELP32_H_INCLUDE
+#  define TLHELP32_H_INCLUDE
+#  include <TLHELP32.h>         /* to get all processes in system */
+#endif
+
 # ifndef NO_GETADAPTERSINFO
 #  include <iphlpapi.h>
 # endif
@@ -480,48 +485,48 @@
     tv.tv_usec = 0;
 
     if (readMode) {
-        n = select (sock + 1, & fds, NULL, NULL, & tv);
+	n = select (sock + 1, & fds, NULL, NULL, & tv);
     } else {
-        n = select (sock + 1, NULL, & fds, NULL, & tv);
+	n = select (sock + 1, NULL, & fds, NULL, & tv);
     }
 
     if (n == 0) {
-        return (0);
+	return (0);
     }
 
     if (n > 0) {
-        return ((FD_ISSET (sock, & fds)) ? 1 : 0);
+	return ((FD_ISSET (sock, & fds)) ? 1 : 0);
     }
 
     winErrNo = WSAGetLastError();
     switch (winErrNo) {
-        case WSAENOTSOCK:
-            if (readMode) {
-
-                DWORD  w = 0;
-                HANDLE h = (HANDLE) _get_osfhandle (aFD);
-
-                if (PeekNamedPipe (h, 0, 0, 0, & w, 0)) {
-                    if( !__isWinNT || w > 0 )
-                        return (1);
-
-                    return (0);
-                }
+	case WSAENOTSOCK:
+	    if (readMode) {
+
+		DWORD  w = 0;
+		HANDLE h = (HANDLE) _get_osfhandle (aFD);
+
+		if (PeekNamedPipe (h, 0, 0, 0, & w, 0)) {
+		    if( !__isWinNT || w > 0 )
+			return (1);
+
+		    return (0);
+		}
 #if 0
-                console_fprintf(stderr, "_canAccessIOWithoutBlocking non Socket\n");
-#endif
-                return (-1);
-            }
-            /* in writeMode we return allways true for none-sockets */
-            return (1);
-
-        case WSAEINPROGRESS:
-        case WSAEWOULDBLOCK:
-            return (0);
-
-        default:
-            console_fprintf(stderr, "_canAccessIOWithoutBlocking -> %d (0x%x)\n", winErrNo, winErrNo);
-            return (-1);
+		console_fprintf(stderr, "_canAccessIOWithoutBlocking non Socket\n");
+#endif
+		return (-1);
+	    }
+	    /* in writeMode we return allways true for none-sockets */
+	    return (1);
+
+	case WSAEINPROGRESS:
+	case WSAEWOULDBLOCK:
+	    return (0);
+
+	default:
+	    console_fprintf(stderr, "_canAccessIOWithoutBlocking -> %d (0x%x)\n", winErrNo, winErrNo);
+	    return (-1);
     }
 
     /* not reached */
@@ -543,7 +548,7 @@
     FARPROC entry;
 
     if (*pLibHandle == NULL) {
-        *pLibHandle = LoadLibrary(libraryName);
+	*pLibHandle = LoadLibrary(libraryName);
     }
     entry = GetProcAddress(*pLibHandle, functionName);
     return entry;
@@ -3247,56 +3252,56 @@
     hasRedirection := (aCommandString isNil or:[aCommandString includesAny:'<>|']).
 
     hasRedirection ifFalse:[
-        "/ test whether the commandString is an executable;
-        "/ then, no shell is required
-        cmdName := aCommandString withoutSeparators.
-        (cmdName notEmpty and:[(cmdName startsWith:$") not]) ifTrue:[
-            |index file suffix|
-
-            index := cmdName indexOfSeparatorStartingAt:1.
-            index ~~ 0 ifTrue:[
-                args := cmdName copyFrom:(index+1).
-                cmdName := cmdName copyFrom:1 to:(index-1).
-            ] ifFalse:[
-                args := ''.
-            ].
-
-            file   := cmdName asFilename.
-            suffix := file suffix.
-
-            suffix isEmptyOrNil ifTrue:[
-                suffix := 'exe'.
-                file := file withSuffix:suffix.
-            ].
-
-            (file exists and:[suffix = 'exe' or:[suffix = 'com']]) ifTrue:[
-                "/ is an executable, no shell required
-                path := file fullAlternativePathName.
-                ^ Array with:path with:aCommandString.
+	"/ test whether the commandString is an executable;
+	"/ then, no shell is required
+	cmdName := aCommandString withoutSeparators.
+	(cmdName notEmpty and:[(cmdName startsWith:$") not]) ifTrue:[
+	    |index file suffix|
+
+	    index := cmdName indexOfSeparatorStartingAt:1.
+	    index ~~ 0 ifTrue:[
+		args := cmdName copyFrom:(index+1).
+		cmdName := cmdName copyFrom:1 to:(index-1).
+	    ] ifFalse:[
+		args := ''.
+	    ].
+
+	    file   := cmdName asFilename.
+	    suffix := file suffix.
+
+	    suffix isEmptyOrNil ifTrue:[
+		suffix := 'exe'.
+		file := file withSuffix:suffix.
+	    ].
+
+	    (file exists and:[suffix = 'exe' or:[suffix = 'com']]) ifTrue:[
+		"/ is an executable, no shell required
+		path := file fullAlternativePathName.
+		^ Array with:path with:aCommandString.
 "/                ^ Array with:path with:(path, ' ', args).
-            ].
-            path := self pathOfCommand:cmdName.
-            path notNil ifTrue:[
-                "/ is an executable, no shell required
-                ^ Array with:path with:aCommandString.
+	    ].
+	    path := self pathOfCommand:cmdName.
+	    path notNil ifTrue:[
+		"/ is an executable, no shell required
+		^ Array with:path with:aCommandString.
 "/                ^ Array with:path with:(path, ' ', args).
-            ].
-        ].
+	    ].
+	].
     ].
 
     shell := self getEnvironment:'COMSPEC'.
     shell isNil ifTrue:[
-        wDir := self getWindowsSystemDirectory asFilename.
-        shell := #('cmd.exe' 'command.com') detect:[:eachCommand|
-                        (wDir / eachCommand) isExecutable
-                    ] ifNone:[
-                        self error:'no cmd.exe available'.
-                    ].
-        shell := (wDir / shell) pathName.
+	wDir := self getWindowsSystemDirectory asFilename.
+	shell := #('cmd.exe' 'command.com') detect:[:eachCommand|
+			(wDir / eachCommand) isExecutable
+		    ] ifNone:[
+			self error:'no cmd.exe available'.
+		    ].
+	shell := (wDir / shell) pathName.
     ].
 
     aCommandString isEmptyOrNil ifTrue:[
-        ^ Array with:shell with:nil
+	^ Array with:shell with:nil
     ].
 
     ^ Array with:shell with:(' /c "' , aCommandString, '"')
@@ -3315,48 +3320,48 @@
     "Internal lowLevel entry for combined fork & exec for WIN32
 
      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.
 
      fdArray 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[0] == StdIn for child
-        fdArray[1] == StdOut for child
-        fdArray[2] == StdErr for child
-        on VMS, these must be channels as returned by createMailBox.
+	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[0] == StdIn for child
+	fdArray[1] == StdOut for child
+	fdArray[2] == StdErr for child
+	on VMS, these must be channels as returned by createMailBox.
 
      NOTE that in WIN32 the fds are HANDLES.
 
      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."
 
     |dirPath rslt|
 
     aDirectory notNil ifTrue:[
-        dirPath := aDirectory asFilename asAbsoluteFilename osNameForDirectory.
-        (dirPath endsWith:':') ifTrue:[
-            dirPath := dirPath , '\'.
-        ].
+	dirPath := aDirectory asFilename asAbsoluteFilename osNameForDirectory.
+	(dirPath endsWith:':') ifTrue:[
+	    dirPath := dirPath , '\'.
+	].
     ].
 
     rslt := self
-        primExec:aCommandPath
-        commandLine:argString
-        fileDescriptors:fdArray
-        fork:doFork
-        newPgrp:newPgrp
-        inPath:dirPath
-        createFlags:nil.
+	primExec:aCommandPath
+	commandLine:argString
+	fileDescriptors:fdArray
+	fork:doFork
+	newPgrp:newPgrp
+	inPath:dirPath
+	createFlags:nil.
 
 "/ 'created ' print. cmdLine print. ' -> ' print. rslt printCR.
     ^ rslt
@@ -3383,34 +3388,34 @@
     |nullStream in out err rslt auxFd|
 
     (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
     ].
 
     rslt := self
-        exec:commandString
-        withArguments:argString
-        environment:anEvironmentDictionary
-        fileDescriptors:(Array with:in fileDescriptor
-                               with:out fileDescriptor
-                               with:err fileDescriptor
-                               with:auxFd)
-        fork:true
-        newPgrp:true "/ false
-        inDirectory:dir.
+	exec:commandString
+	withArguments:argString
+	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
 
@@ -3433,7 +3438,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.
@@ -3568,136 +3573,136 @@
     SECURITY_DESCRIPTOR sd;
 
     if ((__isStringLike(commandPath) || (commandPath == nil)) && __isStringLike(commandLine)) {
-        if (commandPath != nil) {
-            cmdPath = __stringVal(commandPath);
-        }
-        cmdLine = __stringVal(commandLine);
-
-        if (__isStringLike(dirName)) {
-            dir = __stringVal(dirName);
-        }
-
-        /*
-         * create descriptors as req'd
-         */
-        memset(&sa, 0, sizeof (sa));
-        sa.nLength = sizeof( sa );
-        sa.lpSecurityDescriptor = NULL;
-        sa.bInheritHandle = TRUE;
-        InitializeSecurityDescriptor(&sd, SECURITY_DESCRIPTOR_REVISION);
-        SetSecurityDescriptorDacl(&sd, -1, 0, 0);
-
-        sa.lpSecurityDescriptor = &sd;
-        memset(&lppiProcInfo, 0, sizeof (lppiProcInfo));
-
-        memset(&lpsiStartInfo, 0, sizeof (lpsiStartInfo));
-        lpsiStartInfo.cb                = sizeof(lpsiStartInfo);
-        lpsiStartInfo.lpReserved        = NULL;
-        lpsiStartInfo.lpDesktop         = NULL;
-        lpsiStartInfo.lpTitle           = NULL;
-        lpsiStartInfo.dwX               = 0;
-        lpsiStartInfo.dwY               = 0;
-        lpsiStartInfo.dwXSize           = 100;
-        lpsiStartInfo.dwYSize           = 100;
-        lpsiStartInfo.dwXCountChars     = 0;
-        lpsiStartInfo.dwYCountChars     = 0;
-        lpsiStartInfo.dwFillAttribute   = 0;
-        if (0 /*__isWinNT*/) {
-            lpsiStartInfo.dwFlags           = STARTF_USESTDHANDLES;
-            lpsiStartInfo.wShowWindow       = SW_SHOWDEFAULT;
-        } else {
-            lpsiStartInfo.dwFlags           = STARTF_USESHOWWINDOW | STARTF_USESTDHANDLES /*| STARTF_USEPOSITION*/;
-            lpsiStartInfo.wShowWindow       = SW_HIDE /*SW_SHOWDEFAULT*/;
-        }
-        lpsiStartInfo.cbReserved2       = 0;
-        lpsiStartInfo.lpReserved2       = NULL;
-        lpsiStartInfo.hStdInput         = NULL;
-        lpsiStartInfo.hStdOutput        = NULL;
-        lpsiStartInfo.hStdError         = NULL;
-
-        /*
-         * set create process flags
-         * if the flags arg is nil, use common defaults;
-         * if non-nil, it must be a positive integer containing the fdwCreate bits.
-         */
-        if (flagsOrNil != nil) {
-            fdwCreate = __longIntVal(flagsOrNil);
-        } else {
-            if (0 /* __isWinNT */)
-                fdwCreate = 0; //IDLE_PRIORITY_CLASS;
-            else
-                fdwCreate = CREATE_NEW_CONSOLE; //|IDLE_PRIORITY_CLASS; // DETACHED_PROCESS; // NORMAL_PRIORITY_CLASS ;
-
-            if (newPgrp == true) {
-                fdwCreate |= CREATE_NEW_PROCESS_GROUP;
-            }
-            fdwCreate |= CREATE_DEFAULT_ERROR_MODE;
-        }
-
-        if (fdArray == nil) {
-            lpsiStartInfo.hStdInput  = (HANDLE) _get_osfhandle (0);
-            lpsiStartInfo.hStdOutput = (HANDLE) _get_osfhandle (1);
-            lpsiStartInfo.hStdError  = (HANDLE) _get_osfhandle (2);
-        } else if (__isArrayLike(fdArray) && (__arraySize(fdArray) >= 3)) {
-            if (__ArrayInstPtr(fdArray)->a_element[0] != nil) {
-                if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[0])) {
-                    lpsiStartInfo.hStdInput = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[0]);
-                } else {
-                    lpsiStartInfo.hStdInput = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[0]));
-                }
-            }
-            if (__ArrayInstPtr(fdArray)->a_element[1] != nil) {
-                if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[1])) {
-                    lpsiStartInfo.hStdOutput = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[1]);
-                } else {
-                    lpsiStartInfo.hStdOutput = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[1]));
-                }
-            }
-            if (__ArrayInstPtr(fdArray)->a_element[2] != nil) {
-                if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[2])) {
-                    lpsiStartInfo.hStdError  = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[2]);
-                } else {
-                    lpsiStartInfo.hStdError = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[2]));
-                }
-            }
+	if (commandPath != nil) {
+	    cmdPath = __stringVal(commandPath);
+	}
+	cmdLine = __stringVal(commandLine);
+
+	if (__isStringLike(dirName)) {
+	    dir = __stringVal(dirName);
+	}
+
+	/*
+	 * create descriptors as req'd
+	 */
+	memset(&sa, 0, sizeof (sa));
+	sa.nLength = sizeof( sa );
+	sa.lpSecurityDescriptor = NULL;
+	sa.bInheritHandle = TRUE;
+	InitializeSecurityDescriptor(&sd, SECURITY_DESCRIPTOR_REVISION);
+	SetSecurityDescriptorDacl(&sd, -1, 0, 0);
+
+	sa.lpSecurityDescriptor = &sd;
+	memset(&lppiProcInfo, 0, sizeof (lppiProcInfo));
+
+	memset(&lpsiStartInfo, 0, sizeof (lpsiStartInfo));
+	lpsiStartInfo.cb                = sizeof(lpsiStartInfo);
+	lpsiStartInfo.lpReserved        = NULL;
+	lpsiStartInfo.lpDesktop         = NULL;
+	lpsiStartInfo.lpTitle           = NULL;
+	lpsiStartInfo.dwX               = 0;
+	lpsiStartInfo.dwY               = 0;
+	lpsiStartInfo.dwXSize           = 100;
+	lpsiStartInfo.dwYSize           = 100;
+	lpsiStartInfo.dwXCountChars     = 0;
+	lpsiStartInfo.dwYCountChars     = 0;
+	lpsiStartInfo.dwFillAttribute   = 0;
+	if (0 /*__isWinNT*/) {
+	    lpsiStartInfo.dwFlags           = STARTF_USESTDHANDLES;
+	    lpsiStartInfo.wShowWindow       = SW_SHOWDEFAULT;
+	} else {
+	    lpsiStartInfo.dwFlags           = STARTF_USESHOWWINDOW | STARTF_USESTDHANDLES /*| STARTF_USEPOSITION*/;
+	    lpsiStartInfo.wShowWindow       = SW_HIDE /*SW_SHOWDEFAULT*/;
+	}
+	lpsiStartInfo.cbReserved2       = 0;
+	lpsiStartInfo.lpReserved2       = NULL;
+	lpsiStartInfo.hStdInput         = NULL;
+	lpsiStartInfo.hStdOutput        = NULL;
+	lpsiStartInfo.hStdError         = NULL;
+
+	/*
+	 * set create process flags
+	 * if the flags arg is nil, use common defaults;
+	 * if non-nil, it must be a positive integer containing the fdwCreate bits.
+	 */
+	if (flagsOrNil != nil) {
+	    fdwCreate = __longIntVal(flagsOrNil);
+	} else {
+	    if (0 /* __isWinNT */)
+		fdwCreate = 0; //IDLE_PRIORITY_CLASS;
+	    else
+		fdwCreate = CREATE_NEW_CONSOLE; //|IDLE_PRIORITY_CLASS; // DETACHED_PROCESS; // NORMAL_PRIORITY_CLASS ;
+
+	    if (newPgrp == true) {
+		fdwCreate |= CREATE_NEW_PROCESS_GROUP;
+	    }
+	    fdwCreate |= CREATE_DEFAULT_ERROR_MODE;
+	}
+
+	if (fdArray == nil) {
+	    lpsiStartInfo.hStdInput  = (HANDLE) _get_osfhandle (0);
+	    lpsiStartInfo.hStdOutput = (HANDLE) _get_osfhandle (1);
+	    lpsiStartInfo.hStdError  = (HANDLE) _get_osfhandle (2);
+	} else if (__isArrayLike(fdArray) && (__arraySize(fdArray) >= 3)) {
+	    if (__ArrayInstPtr(fdArray)->a_element[0] != nil) {
+		if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[0])) {
+		    lpsiStartInfo.hStdInput = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[0]);
+		} else {
+		    lpsiStartInfo.hStdInput = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[0]));
+		}
+	    }
+	    if (__ArrayInstPtr(fdArray)->a_element[1] != nil) {
+		if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[1])) {
+		    lpsiStartInfo.hStdOutput = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[1]);
+		} else {
+		    lpsiStartInfo.hStdOutput = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[1]));
+		}
+	    }
+	    if (__ArrayInstPtr(fdArray)->a_element[2] != nil) {
+		if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[2])) {
+		    lpsiStartInfo.hStdError  = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[2]);
+		} else {
+		    lpsiStartInfo.hStdError = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[2]));
+		}
+	    }
 #if defined(PROCESSDEBUGWIN32)
-            console_fprintf(stderr, "stdin %x\n", lpsiStartInfo.hStdInput);
-            console_fprintf(stderr, "stdout %x\n",lpsiStartInfo.hStdOutput);
-            console_fprintf(stderr, "stderr %x\n",lpsiStartInfo.hStdError);
-#endif
-        } else {
-            console_fprintf(stderr, "Win32OS [warning]: bad fd arg in createProcess\n");
-        }
-
-        if (doFork == true) {
+	    console_fprintf(stderr, "stdin %x\n", lpsiStartInfo.hStdInput);
+	    console_fprintf(stderr, "stdout %x\n",lpsiStartInfo.hStdOutput);
+	    console_fprintf(stderr, "stderr %x\n",lpsiStartInfo.hStdError);
+#endif
+	} else {
+	    console_fprintf(stderr, "Win32OS [warning]: bad fd arg in createProcess\n");
+	}
+
+	if (doFork == true) {
 #ifdef PROCESSDEBUGWIN32
-            console_fprintf(stderr, "create process cmdPath:<%s> cmdLine:<%s> in <%s>\n", cmdPath, cmdLine, dir);
-#endif
-            if (CreateProcess(  cmdPath,
-                                cmdLine,
-                                &sa, NULL /* &sa */,           /* sec-attribs */
-                                sa.bInheritHandle,  /* inherit handles */
-                                fdwCreate,
-                                NULL,               /* env */
-                                dir,
-                                &lpsiStartInfo,
-                                &lppiProcInfo ))
-            {
-                CloseHandle(lppiProcInfo.hThread);
+	    console_fprintf(stderr, "create process cmdPath:<%s> cmdLine:<%s> in <%s>\n", cmdPath, cmdLine, dir);
+#endif
+	    if (CreateProcess(  cmdPath,
+				cmdLine,
+				&sa, NULL /* &sa */,           /* sec-attribs */
+				sa.bInheritHandle,  /* inherit handles */
+				fdwCreate,
+				NULL,               /* env */
+				dir,
+				&lpsiStartInfo,
+				&lppiProcInfo ))
+	    {
+		CloseHandle(lppiProcInfo.hThread);
 #ifdef PROCESSDEBUGWIN32
-                console_fprintf(stderr, "created process hProcess=%x\n", lppiProcInfo.hProcess);
-#endif
-                __externalAddressVal(handle) = lppiProcInfo.hProcess;
-                ((struct __Win32OperatingSystem__Win32ProcessHandle_struct *)(handle))->pid = __mkSmallInteger(lppiProcInfo.dwProcessId);
-                RETURN (handle);
-            }
+		console_fprintf(stderr, "created process hProcess=%x\n", lppiProcInfo.hProcess);
+#endif
+		__externalAddressVal(handle) = lppiProcInfo.hProcess;
+		((struct __Win32OperatingSystem__Win32ProcessHandle_struct *)(handle))->pid = __mkSmallInteger(lppiProcInfo.dwProcessId);
+		RETURN (handle);
+	    }
 #ifdef PROCESSDEBUGWIN32
-            console_fprintf(stderr, "created process error %d\n", GetLastError());
-#endif
-            RETURN (nil);
-        } else {
-            ; /* should never be called that way */
-        }
+	    console_fprintf(stderr, "created process error %d\n", GetLastError());
+#endif
+	    RETURN (nil);
+	} else {
+	    ; /* should never be called that way */
+	}
     }
 %}.
     "
@@ -3776,12 +3781,12 @@
 
 %{
     if (__isSmallInteger(anIntegerOrHandle)) {
-        close(__intVal(anIntegerOrHandle));
-        RETURN(self);
+	close(__intVal(anIntegerOrHandle));
+	RETURN(self);
     }
     if (__isExternalAddressLike(anIntegerOrHandle)) {
        if (!CloseHandle( __externalAddressVal(anIntegerOrHandle))) {
-           console_fprintf( stderr, "Win32OS [warning]: Could not close handle : %x\n", __externalAddressVal(anIntegerOrHandle));
+	   console_fprintf( stderr, "Win32OS [warning]: Could not close handle : %x\n", __externalAddressVal(anIntegerOrHandle));
        }
        RETURN(self);
     }
@@ -4137,51 +4142,51 @@
 
     if (__isStringLike(fullPathName)) {
 #ifdef DO_WRAP_CALLS
-        {
-            char _aPathName[MAXPATHLEN];
-
-            strncpy(_aPathName, __stringVal(fullPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-            do {
-                __threadErrno = 0;
-                ret = STX_API_NOINT_CALL1( "RemoveDirectoryA", RemoveDirectoryA, _aPathName);
-            } while ((ret < 0) && (__threadErrno == EINTR));
-        }
-#else
-        ret = RemoveDirectoryA((char *)__stringVal(fullPathName));
-        __threadErrno = __WIN32_ERR(GetLastError());
-#endif
-        if (ret != TRUE) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
+	{
+	    char _aPathName[MAXPATHLEN];
+
+	    strncpy(_aPathName, __stringVal(fullPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	    do {
+		__threadErrno = 0;
+		ret = STX_API_NOINT_CALL1( "RemoveDirectoryA", RemoveDirectoryA, _aPathName);
+	    } while ((ret < 0) && (__threadErrno == EINTR));
+	}
+#else
+	ret = RemoveDirectoryA((char *)__stringVal(fullPathName));
+	__threadErrno = __WIN32_ERR(GetLastError());
+#endif
+	if (ret != TRUE) {
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN (false);
+	}
+	RETURN (true);
     }
     if (__isUnicode16String(fullPathName)) {
 #ifdef DO_WRAP_CALLS
-        {
-            wchar_t _wPathName[MAXPATHLEN+1];
-            int i, l;
-
-            l = __unicode16StringSize(fullPathName);
-            if (l > MAXPATHLEN) l = MAXPATHLEN;
-            for (i=0; i<l; i++) {
-                _wPathName[i] = __unicode16StringVal(fullPathName)[i];
-            }
-            _wPathName[i] = 0;
-            do {
-                __threadErrno = 0;
-                ret = STX_API_NOINT_CALL1( "RemoveDirectoryW", RemoveDirectoryW, _wPathName);
-            } while ((ret < 0) && (__threadErrno == EINTR));
-        }
-#else
-        ret = RemoveDirectoryW((char *)__stringVal(fullPathName));
-        __threadErrno = __WIN32_ERR(GetLastError());
-#endif
-        if (ret != TRUE) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
+	{
+	    wchar_t _wPathName[MAXPATHLEN+1];
+	    int i, l;
+
+	    l = __unicode16StringSize(fullPathName);
+	    if (l > MAXPATHLEN) l = MAXPATHLEN;
+	    for (i=0; i<l; i++) {
+		_wPathName[i] = __unicode16StringVal(fullPathName)[i];
+	    }
+	    _wPathName[i] = 0;
+	    do {
+		__threadErrno = 0;
+		ret = STX_API_NOINT_CALL1( "RemoveDirectoryW", RemoveDirectoryW, _wPathName);
+	    } while ((ret < 0) && (__threadErrno == EINTR));
+	}
+#else
+	ret = RemoveDirectoryW((char *)__stringVal(fullPathName));
+	__threadErrno = __WIN32_ERR(GetLastError());
+#endif
+	if (ret != TRUE) {
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN (false);
+	}
+	RETURN (true);
     }
 %}.
     "/
@@ -4205,51 +4210,51 @@
 
     if (__isStringLike(fullPathName)) {
 #ifdef DO_WRAP_CALLS
-        {
-            char _aPathName[MAXPATHLEN];
-
-            strncpy(_aPathName, __stringVal(fullPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-            do {
-                __threadErrno = 0;
-                ret = STX_API_NOINT_CALL1( "DeleteFileA", DeleteFileA, _aPathName);
-            } while ((ret < 0) && (__threadErrno == EINTR));
-        }
-#else
-        ret = DeleteFileA((char *)__stringVal(fullPathName));
-        __threadErrno = __WIN32_ERR(GetLastError());
-#endif
-        if (ret != TRUE) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
+	{
+	    char _aPathName[MAXPATHLEN];
+
+	    strncpy(_aPathName, __stringVal(fullPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	    do {
+		__threadErrno = 0;
+		ret = STX_API_NOINT_CALL1( "DeleteFileA", DeleteFileA, _aPathName);
+	    } while ((ret < 0) && (__threadErrno == EINTR));
+	}
+#else
+	ret = DeleteFileA((char *)__stringVal(fullPathName));
+	__threadErrno = __WIN32_ERR(GetLastError());
+#endif
+	if (ret != TRUE) {
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN (false);
+	}
+	RETURN (true);
     }
     if (__isUnicode16String(fullPathName)) {
 #ifdef DO_WRAP_CALLS
-        {
-            wchar_t _wPathName[MAXPATHLEN+1];
-            int i, l;
-
-            l = __unicode16StringSize(fullPathName);
-            if (l > MAXPATHLEN) l = MAXPATHLEN;
-            for (i=0; i<l; i++) {
-                _wPathName[i] = __unicode16StringVal(fullPathName)[i];
-            }
-            _wPathName[i] = 0;
-            do {
-                __threadErrno = 0;
-                ret = STX_API_NOINT_CALL1( "DeleteFileW", DeleteFileW, _wPathName);
-            } while ((ret < 0) && (__threadErrno == EINTR));
-        }
-#else
-        ret = DeleteFileW((char *)__stringVal(fullPathName));
-        __threadErrno = __WIN32_ERR(GetLastError());
-#endif
-        if (ret != TRUE) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
+	{
+	    wchar_t _wPathName[MAXPATHLEN+1];
+	    int i, l;
+
+	    l = __unicode16StringSize(fullPathName);
+	    if (l > MAXPATHLEN) l = MAXPATHLEN;
+	    for (i=0; i<l; i++) {
+		_wPathName[i] = __unicode16StringVal(fullPathName)[i];
+	    }
+	    _wPathName[i] = 0;
+	    do {
+		__threadErrno = 0;
+		ret = STX_API_NOINT_CALL1( "DeleteFileW", DeleteFileW, _wPathName);
+	    } while ((ret < 0) && (__threadErrno == EINTR));
+	}
+#else
+	ret = DeleteFileW((char *)__stringVal(fullPathName));
+	__threadErrno = __WIN32_ERR(GetLastError());
+#endif
+	if (ret != TRUE) {
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN (false);
+	}
+	RETURN (true);
     }
 
 %}.
@@ -4269,32 +4274,32 @@
 
     if (__isStringLike(oldPath) && __isStringLike(newPath)) {
 #ifdef DO_WRAP_CALLS
-        char _oldPath[MAXPATHLEN], _newPath[MAXPATHLEN];
-
-        strncpy(_oldPath, __stringVal(oldPath), MAXPATHLEN-1); _oldPath[MAXPATHLEN-1] = '\0';
-        strncpy(_newPath, __stringVal(newPath), MAXPATHLEN-1); _newPath[MAXPATHLEN-1] = '\0';
-
-        do {
-            __threadErrno = 0;
-            ret = STX_C_NOINT_CALL2( "rename", rename, _oldPath, _newPath);
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        __BEGIN_INTERRUPTABLE__
-        do {
-            __threadErrno = 0;
-            ret = rename((char *) __stringVal(oldPath), (char *) __stringVal(newPath));
-        } while ((ret < 0) && (__threadErrno == EINTR));
-        __END_INTERRUPTABLE__
-
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        if (ret < 0) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
+	char _oldPath[MAXPATHLEN], _newPath[MAXPATHLEN];
+
+	strncpy(_oldPath, __stringVal(oldPath), MAXPATHLEN-1); _oldPath[MAXPATHLEN-1] = '\0';
+	strncpy(_newPath, __stringVal(newPath), MAXPATHLEN-1); _newPath[MAXPATHLEN-1] = '\0';
+
+	do {
+	    __threadErrno = 0;
+	    ret = STX_C_NOINT_CALL2( "rename", rename, _oldPath, _newPath);
+	} while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	__BEGIN_INTERRUPTABLE__
+	do {
+	    __threadErrno = 0;
+	    ret = rename((char *) __stringVal(oldPath), (char *) __stringVal(newPath));
+	} while ((ret < 0) && (__threadErrno == EINTR));
+	__END_INTERRUPTABLE__
+
+	if (ret < 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
+#endif
+	if (ret < 0) {
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN (false);
+	}
+	RETURN (true);
     }
 %}.
     ^ self primitiveFailed
@@ -4408,7 +4413,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
     "
 
@@ -4418,31 +4423,31 @@
 
     if (__isStringLike(aPathName)) {
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-
-        do {
-            __threadErrno = 0;
-            ret = STX_C_NOINT_CALL2( "stat", stat, _aPathName, &buf);
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        __BEGIN_INTERRUPTABLE__
-        do {
-            __threadErrno = 0;
-            ret = stat( (char *)__stringVal(aPathName), &buf);
-        } while ((ret < 0) && (__threadErrno == EINTR));
-        __END_INTERRUPTABLE__
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-
-        if (ret < 0) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN ( nil );
-        }
-        RETURN ( __mkSmallInteger(buf.st_mode & 0777) );
+	char _aPathName[MAXPATHLEN];
+
+	strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+
+	do {
+	    __threadErrno = 0;
+	    ret = STX_C_NOINT_CALL2( "stat", stat, _aPathName, &buf);
+	} while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	__BEGIN_INTERRUPTABLE__
+	do {
+	    __threadErrno = 0;
+	    ret = stat( (char *)__stringVal(aPathName), &buf);
+	} while ((ret < 0) && (__threadErrno == EINTR));
+	__END_INTERRUPTABLE__
+	if (ret < 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
+#endif
+
+	if (ret < 0) {
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN ( nil );
+	}
+	RETURN ( __mkSmallInteger(buf.st_mode & 0777) );
     }
 %}.
    ^ self primitiveFailed
@@ -4465,30 +4470,30 @@
 
     if (__isStringLike(aPathName) && __isSmallInteger(modeBits)) {
 #ifdef DO_WRAP_CALLS
-        int chmod();
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            ret = STX_C_NOINT_CALL2( "chmod", chmod, _aPathName, __intVal(modeBits));
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        __BEGIN_INTERRUPTABLE__
-        do {
-            __threadErrno = 0;
-            ret = chmod((char *)__stringVal(aPathName), __intVal(modeBits));
-        } while ((ret < 0) && (__threadErrno == EINTR));
-        __END_INTERRUPTABLE__
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        if (ret < 0) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN ( false );
-        }
-        RETURN ( true );
+	int chmod();
+	char _aPathName[MAXPATHLEN];
+
+	strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	do {
+	    __threadErrno = 0;
+	    ret = STX_C_NOINT_CALL2( "chmod", chmod, _aPathName, __intVal(modeBits));
+	} while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	__BEGIN_INTERRUPTABLE__
+	do {
+	    __threadErrno = 0;
+	    ret = chmod((char *)__stringVal(aPathName), __intVal(modeBits));
+	} while ((ret < 0) && (__threadErrno == EINTR));
+	__END_INTERRUPTABLE__
+	if (ret < 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
+#endif
+	if (ret < 0) {
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN ( false );
+	}
+	RETURN ( true );
     }
 %}.
     ^ self primitiveFailed
@@ -4782,13 +4787,13 @@
 
 getDriveType:aPathName
     "returns:
-        0 -> Unknown
-        1 -> Invalid
-        2 -> removable
-        3 -> fixed
-        4 -> remote
-        5 -> cdrom
-        6 -> ramdisk.
+	0 -> Unknown
+	1 -> Invalid
+	2 -> removable
+	3 -> fixed
+	4 -> remote
+	5 -> cdrom
+	6 -> ramdisk.
     This is a stupid interface - do not use."
 
 %{
@@ -4796,20 +4801,20 @@
 
     if (__isStringLike(aPathName)) {
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            ret = STX_API_NOINT_CALL1( "GetDriveType", GetDriveType, _aPathName);
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        ret = GetDriveType((char *) __stringVal(aPathName));
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        RETURN (__MKSMALLINT(ret));
+	char _aPathName[MAXPATHLEN];
+
+	strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	do {
+	    __threadErrno = 0;
+	    ret = STX_API_NOINT_CALL1( "GetDriveType", GetDriveType, _aPathName);
+	} while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	ret = GetDriveType((char *) __stringVal(aPathName));
+	if (ret < 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
+#endif
+	RETURN (__MKSMALLINT(ret));
     }
 %}.
     ^ self primitiveFailed
@@ -4867,35 +4872,35 @@
     wchar_t _aPathName[MAX_PATH+1];
 
     if (__isStringLike(aPathName)) {
-        int i;
-        int l = __stringSize(aPathName);
-        if (l > MAX_PATH) l = MAX_PATH;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __stringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
+	int i;
+	int l = __stringSize(aPathName);
+	if (l > MAX_PATH) l = MAX_PATH;
+
+	for (i=0; i<l; i++) {
+	    _aPathName[i] = __stringVal(aPathName)[i];
+	}
+	_aPathName[i] = 0;
     } else if (__isUnicode16String(aPathName)) {
-        int i;
-        int l = __unicode16StringSize(aPathName);
-        if (l > MAX_PATH) l = MAX_PATH;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
+	int i;
+	int l = __unicode16StringSize(aPathName);
+	if (l > MAX_PATH) l = MAX_PATH;
+
+	for (i=0; i<l; i++) {
+	    _aPathName[i] = __unicode16StringVal(aPathName)[i];
+	}
+	_aPathName[i] = 0;
     } else
-        goto badArgument;
+	goto badArgument;
 
 #ifdef DO_WRAP_CALLS
      do {
-         __threadErrno = 0;
-         ret = STX_API_NOINT_CALL3( "GetLongPathNameW", GetLongPathNameW, _aPathName, _aPathName, MAX_PATH+1);
+	 __threadErrno = 0;
+	 ret = STX_API_NOINT_CALL3( "GetLongPathNameW", GetLongPathNameW, _aPathName, _aPathName, MAX_PATH+1);
      } while ((ret == 0) && (__threadErrno == EINTR));
 #else
      ret = GetLongPathNameW(_aPathName, _aPathName, MAX_PATH+1);
      if (ret == 0) {
-         __threadErrno = __WIN32_ERR(GetLastError());
+	 __threadErrno = __WIN32_ERR(GetLastError());
      }
 #endif
      RETURN ( __MKU16STRING(_aPathName));
@@ -4906,8 +4911,8 @@
 
     "
      self getLongPathName:'x:\'
-     self getLongPathName:'c:\Dokumente und Einstellungen'    
-     self getShortPathName:'c:\Dokumente und Einstellungen'   
+     self getLongPathName:'c:\Dokumente und Einstellungen'
+     self getShortPathName:'c:\Dokumente und Einstellungen'
     "
 !
 
@@ -4925,35 +4930,35 @@
     wchar_t _aPathName[MAX_PATH+1];
 
     if (__isStringLike(aPathName)) {
-        int i;
-        int l = __stringSize(aPathName);
-        if (l > MAX_PATH) l = MAX_PATH;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __stringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
+	int i;
+	int l = __stringSize(aPathName);
+	if (l > MAX_PATH) l = MAX_PATH;
+
+	for (i=0; i<l; i++) {
+	    _aPathName[i] = __stringVal(aPathName)[i];
+	}
+	_aPathName[i] = 0;
     } else if (__isUnicode16String(aPathName)) {
-        int i;
-        int l = __unicode16StringSize(aPathName);
-        if (l > MAX_PATH) l = MAX_PATH;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
+	int i;
+	int l = __unicode16StringSize(aPathName);
+	if (l > MAX_PATH) l = MAX_PATH;
+
+	for (i=0; i<l; i++) {
+	    _aPathName[i] = __unicode16StringVal(aPathName)[i];
+	}
+	_aPathName[i] = 0;
     } else
-        goto badArgument;
+	goto badArgument;
 
 #ifdef DO_WRAP_CALLS
      do {
-         __threadErrno = 0;
-         ret = STX_API_NOINT_CALL3( "GetShortPathNameW", GetShortPathNameW, _aPathName, _aPathName, MAX_PATH+1);
+	 __threadErrno = 0;
+	 ret = STX_API_NOINT_CALL3( "GetShortPathNameW", GetShortPathNameW, _aPathName, _aPathName, MAX_PATH+1);
      } while ((ret == 0) && (__threadErrno == EINTR));
 #else
      ret = GetShortPathNameW(_aPathName, _aPathName, MAX_PATH+1);
      if (ret == 0) {
-         __threadErrno = __WIN32_ERR(GetLastError());
+	 __threadErrno = __WIN32_ERR(GetLastError());
      }
 #endif
      RETURN ( __MKU16STRING(_aPathName));
@@ -4964,8 +4969,8 @@
 
     "
      self getShortPathName:'x:\'
-     self getShortPathName:'c:\Dokumente und Einstellungen' 
-     self getLongPathName:'c:\Dokumente und Einstellungen'   
+     self getShortPathName:'c:\Dokumente und Einstellungen'
+     self getLongPathName:'c:\Dokumente und Einstellungen'
     "
 !
 
@@ -5037,46 +5042,46 @@
 
     if (__isStringLike(aPathName)) {
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            ret = STX_API_NOINT_CALL1( "GetFileAttributesA", GetFileAttributesA, _aPathName);
-        } while ((ret == -1) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesA((char *) __stringVal(aPathName));
-        if (ret == -1) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
+	char _aPathName[MAXPATHLEN];
+
+	strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	do {
+	    __threadErrno = 0;
+	    ret = STX_API_NOINT_CALL1( "GetFileAttributesA", GetFileAttributesA, _aPathName);
+	} while ((ret == -1) && (__threadErrno == EINTR));
+#else
+	ret = GetFileAttributesA((char *) __stringVal(aPathName));
+	if (ret == -1) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
 #endif
     } else if (__isUnicode16String(aPathName)) {
-        wchar_t _wPathName[MAXPATHLEN+1];
-        int i, l;
-
-        l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _wPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _wPathName[i] = 0;
+	wchar_t _wPathName[MAXPATHLEN+1];
+	int i, l;
+
+	l = __unicode16StringSize(aPathName);
+	if (l > MAXPATHLEN) l = MAXPATHLEN;
+	for (i=0; i<l; i++) {
+	    _wPathName[i] = __unicode16StringVal(aPathName)[i];
+	}
+	_wPathName[i] = 0;
 #ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            ret = STX_API_NOINT_CALL1( "GetFileAttributesW", GetFileAttributesW, _wPathName);
-        } while ((ret == -1) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesW(_wPathName);
-        if (ret == -1) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
+	do {
+	    __threadErrno = 0;
+	    ret = STX_API_NOINT_CALL1( "GetFileAttributesW", GetFileAttributesW, _wPathName);
+	} while ((ret == -1) && (__threadErrno == EINTR));
+#else
+	ret = GetFileAttributesW(_wPathName);
+	if (ret == -1) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
 #endif
     } else
-        goto err;
+	goto err;
 
     if (ret < 0) {
-        @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-        RETURN ( false );
+	@global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	RETURN ( false );
     }
     RETURN ( (ret & FILE_ATTRIBUTE_DIRECTORY) ? true : false);
 err:;
@@ -5084,7 +5089,7 @@
     ^ self primitiveFailed
 
     "an alternative implementation would be:
-        ^ (self infoOf:aPathName) type == #directory
+	^ (self infoOf:aPathName) type == #directory
     "
     "
      self isDirectory:'.'
@@ -5128,65 +5133,65 @@
 
 %{
     if (__isStringLike(aPathName)) {
-        int ret;
-
-        /*
-         * under windows, all files are readable ...
-         * so, only check for the files existence here.
-         */
+	int ret;
+
+	/*
+	 * under windows, all files are readable ...
+	 * so, only check for the files existence here.
+	 */
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            ret = STX_API_NOINT_CALL1( "GetFileAttributesA", GetFileAttributesA, _aPathName);
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesA((char *) __stringVal(aPathName));
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        if (ret < 0) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
+	char _aPathName[MAXPATHLEN];
+
+	strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	do {
+	    __threadErrno = 0;
+	    ret = STX_API_NOINT_CALL1( "GetFileAttributesA", GetFileAttributesA, _aPathName);
+	} while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	ret = GetFileAttributesA((char *) __stringVal(aPathName));
+	if (ret < 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
+#endif
+	if (ret < 0) {
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN (false);
+	}
+	RETURN (true);
     }
 
     if (__isUnicode16String(aPathName)) {
-        int ret;
-
-        /*
-         * under windows, all files are readable ...
-         * so, only check for the files existence here.
-         */
-        wchar_t _wPathName[MAXPATHLEN+1];
-        int i, l;
-
-        l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _wPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _wPathName[i] = 0;
+	int ret;
+
+	/*
+	 * under windows, all files are readable ...
+	 * so, only check for the files existence here.
+	 */
+	wchar_t _wPathName[MAXPATHLEN+1];
+	int i, l;
+
+	l = __unicode16StringSize(aPathName);
+	if (l > MAXPATHLEN) l = MAXPATHLEN;
+	for (i=0; i<l; i++) {
+	    _wPathName[i] = __unicode16StringVal(aPathName)[i];
+	}
+	_wPathName[i] = 0;
 #ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            ret = STX_API_NOINT_CALL1( "GetFileAttributesW", GetFileAttributesW, _wPathName);
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesW(_wPathName);
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        if (ret < 0) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
+	do {
+	    __threadErrno = 0;
+	    ret = STX_API_NOINT_CALL1( "GetFileAttributesW", GetFileAttributesW, _wPathName);
+	} while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	ret = GetFileAttributesW(_wPathName);
+	if (ret < 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
+#endif
+	if (ret < 0) {
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN (false);
+	}
+	RETURN (true);
     }
 %}.
     ^ self primitiveFailed
@@ -5221,46 +5226,46 @@
 
     if (__isStringLike(aPathName)) {
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            ret = STX_API_NOINT_CALL1( "GetFileAttributesA", GetFileAttributesA, _aPathName);
-        } while ((ret == -1) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesA((char *) __stringVal(aPathName));
-        if (ret == -1) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
+	char _aPathName[MAXPATHLEN];
+
+	strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	do {
+	    __threadErrno = 0;
+	    ret = STX_API_NOINT_CALL1( "GetFileAttributesA", GetFileAttributesA, _aPathName);
+	} while ((ret == -1) && (__threadErrno == EINTR));
+#else
+	ret = GetFileAttributesA((char *) __stringVal(aPathName));
+	if (ret == -1) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
 #endif
     } else  if (__isUnicode16String(aPathName)) {
-        wchar_t _wPathName[MAXPATHLEN+1];
-        int i, l;
-
-        l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _wPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _wPathName[i] = 0;
+	wchar_t _wPathName[MAXPATHLEN+1];
+	int i, l;
+
+	l = __unicode16StringSize(aPathName);
+	if (l > MAXPATHLEN) l = MAXPATHLEN;
+	for (i=0; i<l; i++) {
+	    _wPathName[i] = __unicode16StringVal(aPathName)[i];
+	}
+	_wPathName[i] = 0;
 #ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            ret = STX_API_NOINT_CALL1( "GetFileAttributesW", GetFileAttributesW, _wPathName);
-        } while ((ret == -1) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesW(_wPathName);
-        if (ret == -1) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
+	do {
+	    __threadErrno = 0;
+	    ret = STX_API_NOINT_CALL1( "GetFileAttributesW", GetFileAttributesW, _wPathName);
+	} while ((ret == -1) && (__threadErrno == EINTR));
+#else
+	ret = GetFileAttributesW(_wPathName);
+	if (ret == -1) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
 #endif
     } else
-        goto err;
+	goto err;
 
     if (ret == -1) {
-        @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-        RETURN ( false );
+	@global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	RETURN ( false );
     }
     RETURN (true);
 
@@ -5299,16 +5304,16 @@
     "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
+	 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
 
      Some of the fields may be returned as nil on systems which do not provide
      all of the information.
@@ -5334,45 +5339,45 @@
     wchar_t _aPathName[MAX_PATH+1];
 
     if (__isStringLike(aPathName)) {
-        int i;
-        int l = __stringSize(aPathName);
-        if (l > MAX_PATH) l = MAX_PATH;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __stringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
+	int i;
+	int l = __stringSize(aPathName);
+	if (l > MAX_PATH) l = MAX_PATH;
+
+	for (i=0; i<l; i++) {
+	    _aPathName[i] = __stringVal(aPathName)[i];
+	}
+	_aPathName[i] = 0;
     } else if (__isUnicode16String(aPathName)) {
-        int i;
-        int l = __unicode16StringSize(aPathName);
-        if (l > MAX_PATH) l = MAX_PATH;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
+	int i;
+	int l = __unicode16StringSize(aPathName);
+	if (l > MAX_PATH) l = MAX_PATH;
+
+	for (i=0; i<l; i++) {
+	    _aPathName[i] = __unicode16StringVal(aPathName)[i];
+	}
+	_aPathName[i] = 0;
     } else
-        goto badArgument;
+	goto badArgument;
 
 #ifdef DO_WRAP_CALLS
     {
-        do {
-            __threadErrno = 0;
-            result = STX_API_NOINT_CALL3( "GetFileAttributesExW", GetFileAttributesExW, _aPathName, GetFileExInfoStandard, &fileAttributeData);
-        } while (!result && (__threadErrno == EINTR));
+	do {
+	    __threadErrno = 0;
+	    result = STX_API_NOINT_CALL3( "GetFileAttributesExW", GetFileAttributesExW, _aPathName, GetFileExInfoStandard, &fileAttributeData);
+	} while (!result && (__threadErrno == EINTR));
     }
 #else
     result = GetFileAttributesExW(_aPathName, GetFileExInfoStandard, &fileAttributeData);
     if (!result) {
-        __threadErrno = __WIN32_ERR(GetLastError());
+	__threadErrno = __WIN32_ERR(GetLastError());
     }
 #endif
 
     if (!result) {
-        @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	@global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
     } else {
-        id = __mkSmallInteger(0);   /* could get it by opening ... */
-        size = __MKLARGEINT64(1, fileAttributeData.nFileSizeLow, fileAttributeData.nFileSizeHigh);
+	id = __mkSmallInteger(0);   /* could get it by opening ... */
+	size = __MKLARGEINT64(1, fileAttributeData.nFileSizeLow, fileAttributeData.nFileSizeHigh);
 
 //        if (fileAttributeData.cFileName[0] != '\0') {
 //            bcopy(fileAttributeData.cFileName, fileNameBuffer, MAX_PATH*sizeof(wchar_t));
@@ -5386,83 +5391,83 @@
 //            alternativeName = __MKU16STRING(alternativeFileNameBuffer); /* DOS name */
 //        }
 
-        /*
-         * simulate access bits
-         */
-        if (fileAttributeData.dwFileAttributes & FILE_ATTRIBUTE_READONLY) {
-            modeBits = 0444;
-        } else {
-            modeBits = 0666;
-        }
-
-        if (fileAttributeData.dwFileAttributes & FILE_ATTRIBUTE_DIRECTORY) {
-            type = @symbol(directory);
-            modeBits = 0777;   /* executable and WRITABLE - refer to comment in #isWritable: */
-        } else if (fileAttributeData.dwFileAttributes & FILE_ATTRIBUTE_REPARSE_POINT) {
-            type = @symbol(symbolicLink);
-            modeBits = 0777;   /* even in UNIX symlinks have 0777 */
-        } else {
-            type = @symbol(regular);
-        }
-
-        mode = __mkSmallInteger(modeBits);
-
-        cOsTime = FileTimeToOsTime(&fileAttributeData.ftCreationTime);
-        aOsTime = FileTimeToOsTime(&fileAttributeData.ftLastAccessTime);
-        mOsTime = FileTimeToOsTime(&fileAttributeData.ftLastWriteTime);
+	/*
+	 * simulate access bits
+	 */
+	if (fileAttributeData.dwFileAttributes & FILE_ATTRIBUTE_READONLY) {
+	    modeBits = 0444;
+	} else {
+	    modeBits = 0666;
+	}
+
+	if (fileAttributeData.dwFileAttributes & FILE_ATTRIBUTE_DIRECTORY) {
+	    type = @symbol(directory);
+	    modeBits = 0777;   /* executable and WRITABLE - refer to comment in #isWritable: */
+	} else if (fileAttributeData.dwFileAttributes & FILE_ATTRIBUTE_REPARSE_POINT) {
+	    type = @symbol(symbolicLink);
+	    modeBits = 0777;   /* even in UNIX symlinks have 0777 */
+	} else {
+	    type = @symbol(regular);
+	}
+
+	mode = __mkSmallInteger(modeBits);
+
+	cOsTime = FileTimeToOsTime(&fileAttributeData.ftCreationTime);
+	aOsTime = FileTimeToOsTime(&fileAttributeData.ftLastAccessTime);
+	mOsTime = FileTimeToOsTime(&fileAttributeData.ftLastWriteTime);
     }
 
   badArgument: ;
 %}.
 
     (aPathName endsWith:'.lnk') ifTrue:[
-        type := #symbolicLink.
-        "/ now done lazyly in FileStatusInfo, when the path is accessed
-        "/ path := self getLinkTarget:aPathName.
+	type := #symbolicLink.
+	"/ now done lazyly in FileStatusInfo, when the path is accessed
+	"/ path := self getLinkTarget:aPathName.
     ].
 
     mode isNil ifTrue:[
-        (self isDirectory:aPathName) ifTrue:[
-            "/ the code above fails for root directories (these do not exist).
-            "/ simulate here
-            mode := 8r777.
-            type := #directory.
-            uid := gid := 0.
-            size := 0.
-            id := 0.
-            atime := mtime := ctime := Timestamp now.
-        ].
+	(self isDirectory:aPathName) ifTrue:[
+	    "/ the code above fails for root directories (these do not exist).
+	    "/ simulate here
+	    mode := 8r777.
+	    type := #directory.
+	    uid := gid := 0.
+	    size := 0.
+	    id := 0.
+	    atime := mtime := ctime := Timestamp now.
+	].
     ].
     mode notNil ifTrue:[
-        atime isNil ifTrue:[
-            atime := Timestamp new fromOSTime:aOsTime.
-        ].
-        mtime isNil ifTrue:[
-            mtime := Timestamp new fromOSTime:mOsTime.
-        ].
-        ctime isNil ifTrue:[
-            ctime := Timestamp new fromOSTime:cOsTime.
-        ].
-        fileName notNil ifTrue:[
-            fileName := fileName asSingleByteStringIfPossible
-        ].
-        alternativeName notNil ifTrue:[
-            alternativeName := alternativeName asSingleByteStringIfPossible
-        ].
-        info := FileStatusInfo
-                    type:type
-                    mode:mode
-                    uid:uid
-                    gid:gid
-                    size:size
-                    id:id
-                    accessed:atime
-                    modified:mtime
-                    created:ctime
-                    sourcePath:aPathName
-                    fullName:fileName
-                    alternativeName:alternativeName.
-        ^ info
+	atime isNil ifTrue:[
+	    atime := Timestamp new fromOSTime:aOsTime.
+	].
+	mtime isNil ifTrue:[
+	    mtime := Timestamp new fromOSTime:mOsTime.
+	].
+	ctime isNil ifTrue:[
+	    ctime := Timestamp new fromOSTime:cOsTime.
+	].
+	fileName notNil ifTrue:[
+	    fileName := fileName asSingleByteStringIfPossible
+	].
+	alternativeName notNil ifTrue:[
+	    alternativeName := alternativeName asSingleByteStringIfPossible
+	].
+	info := FileStatusInfo
+		    type:type
+		    mode:mode
+		    uid:uid
+		    gid:gid
+		    size:size
+		    id:id
+		    accessed:atime
+		    modified:mtime
+		    created:ctime
+		    sourcePath:aPathName
+		    fullName:fileName
+		    alternativeName:alternativeName.
+	^ info
    ].
    ^ nil
 
@@ -5583,52 +5588,52 @@
 
     if (__isStringLike(aPathName)) {
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            ret = STX_API_NOINT_CALL1( "GetFileAttributesA", GetFileAttributesA, _aPathName);
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesA((char *) __stringVal(aPathName));
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        if (ret >= 0) {
-            RETURN ( __mkSmallInteger(ret) );
-        }
-        __threadErrno = __WIN32_ERR(GetLastError());
-        RETURN (nil);
+	char _aPathName[MAXPATHLEN];
+
+	strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	do {
+	    __threadErrno = 0;
+	    ret = STX_API_NOINT_CALL1( "GetFileAttributesA", GetFileAttributesA, _aPathName);
+	} while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	ret = GetFileAttributesA((char *) __stringVal(aPathName));
+	if (ret < 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
+#endif
+	if (ret >= 0) {
+	    RETURN ( __mkSmallInteger(ret) );
+	}
+	__threadErrno = __WIN32_ERR(GetLastError());
+	RETURN (nil);
     }
 
     if (__isUnicode16String(aPathName)) {
-        wchar_t _wPathName[MAXPATHLEN+1];
-        int i, l;
-
-        l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _wPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _wPathName[i] = 0;
+	wchar_t _wPathName[MAXPATHLEN+1];
+	int i, l;
+
+	l = __unicode16StringSize(aPathName);
+	if (l > MAXPATHLEN) l = MAXPATHLEN;
+	for (i=0; i<l; i++) {
+	    _wPathName[i] = __unicode16StringVal(aPathName)[i];
+	}
+	_wPathName[i] = 0;
 #ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            ret = STX_API_NOINT_CALL1( "GetFileAttributesW", GetFileAttributesW, _wPathName);
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesW(_wPathName);
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        if (ret >= 0) {
-            RETURN ( __mkSmallInteger(ret) );
-        }
-        __threadErrno = __WIN32_ERR(GetLastError());
-        RETURN (nil);
+	do {
+	    __threadErrno = 0;
+	    ret = STX_API_NOINT_CALL1( "GetFileAttributesW", GetFileAttributesW, _wPathName);
+	} while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	ret = GetFileAttributesW(_wPathName);
+	if (ret < 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
+#endif
+	if (ret >= 0) {
+	    RETURN ( __mkSmallInteger(ret) );
+	}
+	__threadErrno = __WIN32_ERR(GetLastError());
+	RETURN (nil);
     }
 %}.
     ^ self primitiveFailed
@@ -5658,102 +5663,102 @@
 
 %{  /* xxSTACK: 16000 */
     if (__isStringLike(aPathName)) {
-        char nameBuffer[MAXPATHLEN + 1 + MAXPATHLEN + 1];
-        char *pFinal;
-        int rslt;
+	char nameBuffer[MAXPATHLEN + 1 + MAXPATHLEN + 1];
+	char *pFinal;
+	int rslt;
 
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            rslt = STX_API_NOINT_CALL4( "GetFullPathName", GetFullPathName, _aPathName, sizeof(nameBuffer), nameBuffer, &pFinal);
-        } while ((rslt < 0) && (__threadErrno == EINTR));
-#else
-        rslt = GetFullPathName(__stringVal(aPathName), sizeof(nameBuffer), nameBuffer, &pFinal);
-#endif
-
-        if (rslt > 0) {
-            /*
-             * Attention: GetLongPathName is not available on old NT4.0/W95/W98
-             */
-            static FARPROC GetLongPathName_entry = NULL;
+	char _aPathName[MAXPATHLEN];
+
+	strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	do {
+	    __threadErrno = 0;
+	    rslt = STX_API_NOINT_CALL4( "GetFullPathName", GetFullPathName, _aPathName, sizeof(nameBuffer), nameBuffer, &pFinal);
+	} while ((rslt < 0) && (__threadErrno == EINTR));
+#else
+	rslt = GetFullPathName(__stringVal(aPathName), sizeof(nameBuffer), nameBuffer, &pFinal);
+#endif
+
+	if (rslt > 0) {
+	    /*
+	     * Attention: GetLongPathName is not available on old NT4.0/W95/W98
+	     */
+	    static FARPROC GetLongPathName_entry = NULL;
 #ifdef NO_NT4_0_COMPATIBILITY
-            GetLongPathName_entry = (FARPROC) GetLongPathName;
-#else
-            if (GetLongPathName_entry == NULL) {
-                GetLongPathName_entry = __get_kernel32_functionAddress("GetLongPathNameA");
-            }
+	    GetLongPathName_entry = (FARPROC) GetLongPathName;
+#else
+	    if (GetLongPathName_entry == NULL) {
+		GetLongPathName_entry = __get_kernel32_functionAddress("GetLongPathNameA");
+	    }
 #endif /* NO_NT4_0_COMPATIBILITY */
 
-            if (GetLongPathName_entry) {
+	    if (GetLongPathName_entry) {
 #ifdef DO_WRAP_CALLS
-                do {
-                    __threadErrno = 0;
-                    rslt = STX_API_NOINT_CALL3( "GetLongPathName", GetLongPathName_entry, nameBuffer, nameBuffer, sizeof(nameBuffer));
-                } while ((rslt < 0) && (__threadErrno == EINTR));
-#else
-                rslt = (*GetLongPathName_entry)(nameBuffer, nameBuffer, sizeof(nameBuffer));
-#endif
-            }
-        }
-        if (rslt > 0) {
-            RETURN ( __MKSTRING(nameBuffer) );
-        }
-        __threadErrno = __WIN32_ERR(GetLastError());
-        RETURN (nil);
+		do {
+		    __threadErrno = 0;
+		    rslt = STX_API_NOINT_CALL3( "GetLongPathName", GetLongPathName_entry, nameBuffer, nameBuffer, sizeof(nameBuffer));
+		} while ((rslt < 0) && (__threadErrno == EINTR));
+#else
+		rslt = (*GetLongPathName_entry)(nameBuffer, nameBuffer, sizeof(nameBuffer));
+#endif
+	    }
+	}
+	if (rslt > 0) {
+	    RETURN ( __MKSTRING(nameBuffer) );
+	}
+	__threadErrno = __WIN32_ERR(GetLastError());
+	RETURN (nil);
     }
     if (__isUnicode16String(aPathName)) {
-        wchar_t nameBuffer[MAXPATHLEN + 1 + MAXPATHLEN + 1];
-        char *pFinal;
-        int rslt;
-        wchar_t _aPathName[MAXPATHLEN+1];
-        int i, l;
-
-        l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
+	wchar_t nameBuffer[MAXPATHLEN + 1 + MAXPATHLEN + 1];
+	char *pFinal;
+	int rslt;
+	wchar_t _aPathName[MAXPATHLEN+1];
+	int i, l;
+
+	l = __unicode16StringSize(aPathName);
+	if (l > MAXPATHLEN) l = MAXPATHLEN;
+	for (i=0; i<l; i++) {
+	    _aPathName[i] = __unicode16StringVal(aPathName)[i];
+	}
+	_aPathName[i] = 0;
 
 #ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            rslt = STX_API_NOINT_CALL4( "GetFullPathNameW", GetFullPathNameW, _aPathName, MAXPATHLEN, nameBuffer, &pFinal);
-        } while ((rslt < 0) && (__threadErrno == EINTR));
-#else
-        rslt = GetFullPathName(_aPathName, MAXPATHLEN, nameBuffer, &pFinal);
-#endif
-        if (rslt > 0) {
-            /*
-             * Attention: GetLongPathName is not available on old NT4.0/W95/W98
-             */
-            static FARPROC GetLongPathNameW_entry = NULL;
+	do {
+	    __threadErrno = 0;
+	    rslt = STX_API_NOINT_CALL4( "GetFullPathNameW", GetFullPathNameW, _aPathName, MAXPATHLEN, nameBuffer, &pFinal);
+	} while ((rslt < 0) && (__threadErrno == EINTR));
+#else
+	rslt = GetFullPathName(_aPathName, MAXPATHLEN, nameBuffer, &pFinal);
+#endif
+	if (rslt > 0) {
+	    /*
+	     * Attention: GetLongPathName is not available on old NT4.0/W95/W98
+	     */
+	    static FARPROC GetLongPathNameW_entry = NULL;
 #ifdef NO_NT4_0_COMPATIBILITY
-            GetLongPathNameW_entry = (FARPROC) GetLongPathNameW;
-#else
-            if (GetLongPathNameW_entry == NULL) {
-                GetLongPathNameW_entry = __get_kernel32_functionAddress("GetLongPathNameW");
-            }
+	    GetLongPathNameW_entry = (FARPROC) GetLongPathNameW;
+#else
+	    if (GetLongPathNameW_entry == NULL) {
+		GetLongPathNameW_entry = __get_kernel32_functionAddress("GetLongPathNameW");
+	    }
 #endif /* NO_NT4_0_COMPATIBILITY */
 
-            if (GetLongPathNameW_entry) {
+	    if (GetLongPathNameW_entry) {
 #ifdef DO_WRAP_CALLS
-                do {
-                    __threadErrno = 0;
-                    rslt = STX_API_NOINT_CALL3( "GetLongPathNameW", GetLongPathNameW_entry, nameBuffer, nameBuffer, MAXPATHLEN);
-                } while ((rslt < 0) && (__threadErrno == EINTR));
-#else
-                rslt = (*GetLongPathNameW_entry)(nameBuffer, nameBuffer, MAXPATHLEN);
-#endif
-            }
-        }
-        if (rslt > 0) {
-            RETURN ( __MKU16STRING(nameBuffer) );
-        }
-        __threadErrno = __WIN32_ERR(GetLastError());
+		do {
+		    __threadErrno = 0;
+		    rslt = STX_API_NOINT_CALL3( "GetLongPathNameW", GetLongPathNameW_entry, nameBuffer, nameBuffer, MAXPATHLEN);
+		} while ((rslt < 0) && (__threadErrno == EINTR));
+#else
+		rslt = (*GetLongPathNameW_entry)(nameBuffer, nameBuffer, MAXPATHLEN);
+#endif
+	    }
+	}
+	if (rslt > 0) {
+	    RETURN ( __MKU16STRING(nameBuffer) );
+	}
+	__threadErrno = __WIN32_ERR(GetLastError());
     }
 %}.
     ^ nil
@@ -5791,55 +5796,55 @@
     int ret;
 
     if (__isSmallInteger(anInteger)) {
-        if (__isStringLike(aPathName)) {
+	if (__isStringLike(aPathName)) {
 #ifdef DO_WRAP_CALLS
-            char _aPathName[MAXPATHLEN];
-
-            strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-            do {
-                __threadErrno = 0;
-                ret = STX_API_NOINT_CALL2( "SetFileAttributesA", SetFileAttributesA, _aPathName, __intVal(anInteger) );
-            } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-            ret = SetFileAttributesA((char *) __stringVal(aPathName), __intVal(anInteger));
-            if (ret < 0) {
-                __threadErrno = __WIN32_ERR(GetLastError());
-            }
-#endif
-            if (ret >= 0) {
-                RETURN ( true );
-            }
-            __threadErrno = __WIN32_ERR(GetLastError());
-            RETURN (false);
-        }
-
-        if (__isUnicode16String(aPathName)) {
-            wchar_t _wPathName[MAXPATHLEN+1];
-            int i, l;
-
-            l = __unicode16StringSize(aPathName);
-            if (l > MAXPATHLEN) l = MAXPATHLEN;
-            for (i=0; i<l; i++) {
-                _wPathName[i] = __unicode16StringVal(aPathName)[i];
-            }
-            _wPathName[i] = 0;
+	    char _aPathName[MAXPATHLEN];
+
+	    strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	    do {
+		__threadErrno = 0;
+		ret = STX_API_NOINT_CALL2( "SetFileAttributesA", SetFileAttributesA, _aPathName, __intVal(anInteger) );
+	    } while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	    ret = SetFileAttributesA((char *) __stringVal(aPathName), __intVal(anInteger));
+	    if (ret < 0) {
+		__threadErrno = __WIN32_ERR(GetLastError());
+	    }
+#endif
+	    if (ret >= 0) {
+		RETURN ( true );
+	    }
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	    RETURN (false);
+	}
+
+	if (__isUnicode16String(aPathName)) {
+	    wchar_t _wPathName[MAXPATHLEN+1];
+	    int i, l;
+
+	    l = __unicode16StringSize(aPathName);
+	    if (l > MAXPATHLEN) l = MAXPATHLEN;
+	    for (i=0; i<l; i++) {
+		_wPathName[i] = __unicode16StringVal(aPathName)[i];
+	    }
+	    _wPathName[i] = 0;
 #ifdef DO_WRAP_CALLS
-            do {
-                __threadErrno = 0;
-                ret = STX_API_NOINT_CALL2( "SetFileAttributesW", SetFileAttributesW, _wPathName, __intVal(anInteger) );
-            } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-            ret = SetFileAttributesW(_wPathName, __intVal(anInteger));
-            if (ret < 0) {
-                __threadErrno = __WIN32_ERR(GetLastError());
-            }
-#endif
-            if (ret >= 0) {
-                RETURN ( true );
-            }
-            __threadErrno = __WIN32_ERR(GetLastError());
-            RETURN (false);
-        }
+	    do {
+		__threadErrno = 0;
+		ret = STX_API_NOINT_CALL2( "SetFileAttributesW", SetFileAttributesW, _wPathName, __intVal(anInteger) );
+	    } while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	    ret = SetFileAttributesW(_wPathName, __intVal(anInteger));
+	    if (ret < 0) {
+		__threadErrno = __WIN32_ERR(GetLastError());
+	    }
+#endif
+	    if (ret >= 0) {
+		RETURN ( true );
+	    }
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	    RETURN (false);
+	}
     }
 %}.
     ^ self primitiveFailed
@@ -5847,9 +5852,9 @@
 
 setCurrentDirectory:pathName
     pathName bitsPerCharacter == 16 ifTrue:[
-        self primSetCurrentDirectoryW:(pathName copyWith:(Character value:0))
+	self primSetCurrentDirectoryW:(pathName copyWith:(Character value:0))
     ] ifFalse:[
-        self primSetCurrentDirectoryA:pathName
+	self primSetCurrentDirectoryA:pathName
     ].
 
     "
@@ -6121,8 +6126,8 @@
 
 %{
     while(1) {
-        console_printf("blocking...");
-        STX_API_CALL1("Sleep", Sleep, 50);
+	console_printf("blocking...");
+	STX_API_CALL1("Sleep", Sleep, 50);
     }
 %}.
     "
@@ -6139,7 +6144,7 @@
     int ret;
 
     do {
-        ret = STX_API_NOINT_CALL1("Sleep", Sleep, 60000);
+	ret = STX_API_NOINT_CALL1("Sleep", Sleep, 60000);
     } while (ret < 0 && __threadErrno == EINTR);
 %}.
     "
@@ -6156,7 +6161,7 @@
     int ret;
 
     do {
-        ret = STX_API_CALL1("Sleep", Sleep, 60000);
+	ret = STX_API_CALL1("Sleep", Sleep, 60000);
     } while (ret < 0 && __threadErrno == EINTR);
 %}.
     "
@@ -6554,7 +6559,7 @@
     ^ self primitiveFailed
 !
 
-terminateProcess:processHandle
+terminateProcess:processHandleOrPid
     "terminate a process.
      The process has a chance to do some cleanup.
      WIN32:
@@ -6569,10 +6574,10 @@
 	 may be compromised if TerminateProcess is used.
      TODO: send it a WM_QUIT instead, to allow for proper shutdown."
 
-    self terminateProcess:processHandle exitCode:0
-!
-
-terminateProcess:processHandle exitCode:exitCode
+    self terminateProcess:processHandleOrPid exitCode:0
+!
+
+terminateProcess:processHandleOrPid exitCode:exitCode
     "terminate a process.
      The process should have a chance to do some cleanup.
      WIN32:
@@ -6588,52 +6593,53 @@
      TODO: send it a WM_QUIT instead, to allow for proper shutdown."
 
 %{
-    if (__isExternalAddressLike(processHandle) ) {
-	HANDLE hProcess = _HANDLEVal(processHandle);
-
-#ifdef PROCESS1DEBUGWIN32
-	console_printf("TerminateProcess handle: %x\n", hProcess);
-#endif
+    if (__isExternalAddressLike(processHandleOrPid) ) {
+	HANDLE hProcess = _HANDLEVal(processHandleOrPid);
+
 	if (hProcess != 0) {
-	    TerminateProcess(hProcess, __intVal(exitCode));
-	} else {
-	    console_fprintf(stderr, "Win32OS [warning]: wrong hProcess in TerminateProcess\n");
-	}
-    } else {
-	console_fprintf(stderr, "Win32OS [warning]: wrong processHandle in TerminateProcess\n");
-    }
-%}
+	    TerminateProcess( hProcess, __intVal(exitCode) );
+	}
+	RETURN( true );
+    } else if( __isSmallInteger(processHandleOrPid) ) {
+	HANDLE hProcess = OpenProcess(PROCESS_TERMINATE, 0, __smallIntegerVal(processHandleOrPid));
+
+	if( hProcess != 0 ) {
+	    TerminateProcess( hProcess, __intVal(exitCode) );
+	    CloseHandle(hProcess);
+	}
+	RETURN( true );
+    }
+%}.
+    self primitiveFailed:#invalidParameter.
+
 
     "Modified: / 28.12.1995 / 15:05:37 / stefan"
     "Modified: / 27.1.1998 / 20:05:47 / cg"
 !
 
-terminateProcessGroup:processGroupHandle
+terminateProcessGroup:processGroupHandleOrPid
     "terminate a process group.
      The processes should have a chance to do some cleanup.
      WIN32:
 	 The processGroup is terminated by sending it a CTRL-C
 	 using GenerateConsoleCtrlEvent."
 
-%{
-    if (__isExternalAddressLike(processGroupHandle) ) {
-	HANDLE hProcessGroup = _HANDLEVal(processGroupHandle);
-	DWORD processGroupId;
-
-	if (hProcessGroup != (HANDLE)0) {
-	    processGroupId = __intVal( ((struct __Win32OperatingSystem__Win32ProcessHandle_struct *)(processGroupHandle))->pid );
-
-#ifdef PROCESS1DEBUGWIN32
-	    console_printf("TerminateProcessGroup processGroupHandle: %x (%d)\n", hProcessGroup, processGroupId);
-#endif
-	    GenerateConsoleCtrlEvent(CTRL_C_EVENT, processGroupId);
-	} else {
-	    console_fprintf(stderr, "Win32OS [warning]: wrong hProcessGroup in TerminateProcessGroup \n");
-	}
-    } else {
-	console_fprintf(stderr, "Win32OS [warning]: wrong processGroupHandle in TerminateProcessGroup \n");
-    }
-%}
+    | pid list |
+
+    list := self getAllProcesses.
+    list size == 0 ifTrue:[^ self ].
+
+    processGroupHandleOrPid isInteger ifTrue:[
+	pid := processGroupHandleOrPid
+    ] ifFalse:[
+	pid := processGroupHandleOrPid pid.
+    ].
+    list do:[:anOSProcess |
+	( anOSProcess parentPid == pid ) ifTrue:[
+	    self terminateProcess:( anOSProcess pid ).
+	].
+    ].
+
 ! !
 
 !Win32OperatingSystem class methodsFor:'ipc support'!
@@ -6658,8 +6664,8 @@
     sa.bInheritHandle = TRUE;
 
     if( ! CreatePipe( &pipeRead, &pipeWrite, &sa, 0 ) ) {
-        @global(LastErrorNumber) = error = __mkSmallInteger( __WIN32_ERR(GetLastError()) );
-        goto out;
+	@global(LastErrorNumber) = error = __mkSmallInteger( __WIN32_ERR(GetLastError()) );
+	goto out;
     }
 
 #if 1
@@ -6679,9 +6685,9 @@
 out:;
 %}.
     (fd1 notNil and:[fd2 notNil]) ifTrue:[
-        (fd1 ~~ -1 and:[fd2 ~~ -1]) ifTrue:[
-            ^ Array with:fd1 with:fd2.
-        ].
+	(fd1 ~~ -1 and:[fd2 ~~ -1]) ifTrue:[
+	    ^ Array with:fd1 with:fd2.
+	].
     ].
 
     ^ nil
@@ -6733,6 +6739,41 @@
     "Created: / 18-09-2007 / 16:34:25 / cg"
 !
 
+getAllProcesses
+    "answer a sequence of OSProcess, all processes running in system"
+
+    |list st_perProc|
+
+    list := OrderedCollection new.
+
+%{
+#ifdef TLHELP32_H_INCLUDE
+
+    HANDLE hProcessSnap;
+    PROCESSENTRY32 pe32;
+    hProcessSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0);
+
+    if( hProcessSnap != INVALID_HANDLE_VALUE ) {
+	pe32.dwSize = sizeof(PROCESSENTRY32);
+	Process32First( hProcessSnap, & pe32 );
+
+	do {
+	    st_perProc = __SSEND0(@global(OSProcess), @symbol(new), 0);
+
+	    __SSEND1(st_perProc, @symbol(commandLine:), 0, __MKSTRING(pe32.szExeFile) );
+	    __SSEND1(st_perProc, @symbol(pid:), 0, __mkSmallInteger(pe32.th32ProcessID) );
+	    __SSEND1(st_perProc, @symbol(parentPid:), 0, __mkSmallInteger(pe32.th32ParentProcessID) );
+
+	    __SSEND1(list, @symbol(add:), 0, st_perProc );
+	}
+	while(Process32Next(hProcessSnap,&pe32));
+    }
+#endif  /* TLHELP32_H_INCLUDE */
+
+%}.
+    ^ list
+!
+
 getCurrentProcess
     <apicall: handle "GetCurrentProcess" ( ) module: "kernel32.dll" >
 
@@ -7659,14 +7700,14 @@
     "answer the number of physical processors in the system"
 
     %{
-        SYSTEM_INFO sInfo;
-        GetSystemInfo(&sInfo);
-
-        return __mkSmallInteger(sInfo.dwNumberOfProcessors);
+	SYSTEM_INFO sInfo;
+	GetSystemInfo(&sInfo);
+
+	return __mkSmallInteger(sInfo.dwNumberOfProcessors);
     %}.
 
     "
-        self getNumberOfProcessors
+	self getNumberOfProcessors
     "
 !
 
@@ -8080,7 +8121,7 @@
 hasConsole
     "return true, if there is some kind of console available
      (i.e. for proper stdIn, stdOut and stdErr handling).
-     This only returns false when running únder windows, and
+     This only returns false when running nder windows, and
      the system is running as a pure windows application.
      If false, the miniDebugger is useless and not used."
 
@@ -8128,28 +8169,28 @@
     int err;
 
     if (__isSmallInteger(pid)) {
-        // assume, that synchronize needs less privilege...
-        processHandle = OpenProcess(SYNCHRONIZE, FALSE, __smallIntegerVal(pid));
-        if (processHandle) {
-            CloseHandle(processHandle);
-            RETURN(true);
-        }
-
-        err = GetLastError();
-        // we do not have access to the process (so pid does exist ;-))
-        if (err == ERROR_ACCESS_DENIED) {
-            RETURN(true);
-        }
-        // pid does not exist
-        if (err == ERROR_INVALID_PARAMETER) {
-            RETURN(false);
-        }
-
-        // any other error - raise signal
-        __threadErrno = __WIN32_ERR(err);
-        error = __mkSmallInteger(__threadErrno);
+	// assume, that synchronize needs less privilege...
+	processHandle = OpenProcess(SYNCHRONIZE, FALSE, __smallIntegerVal(pid));
+	if (processHandle) {
+	    CloseHandle(processHandle);
+	    RETURN(true);
+	}
+
+	err = GetLastError();
+	// we do not have access to the process (so pid does exist ;-))
+	if (err == ERROR_ACCESS_DENIED) {
+	    RETURN(true);
+	}
+	// pid does not exist
+	if (err == ERROR_INVALID_PARAMETER) {
+	    RETURN(false);
+	}
+
+	// any other error - raise signal
+	__threadErrno = __WIN32_ERR(err);
+	error = __mkSmallInteger(__threadErrno);
     } else {
-        error = @symbol(invalidParameter);
+	error = @symbol(invalidParameter);
     }
 %}.
 
@@ -8356,18 +8397,18 @@
     "
 !
 
-randomBytesInto:bufferOrInteger 
+randomBytesInto:bufferOrInteger
     "If bufferOrInteger is a String or a ByteArray,
-        fill a given buffer with random bytes from the RtlGenRandom function
-        and nswer the buffer.
+	fill a given buffer with random bytes from the RtlGenRandom function
+	and nswer the buffer.
 
      If bufferOrInteger is a SmallInteger,
-        return this many bytes (max 4) as a SmallInteger.
-
-     Return nil on error (and raise PrimitiveFailure).   
+	return this many bytes (max 4) as a SmallInteger.
+
+     Return nil on error (and raise PrimitiveFailure).
 
      NOTE: This is a private interface, please use RandomGenerator!!"
-    
+
 %{
 //    BOOLEAN RtlGenRandom(
 //      __out  PVOID RandomBuffer,
@@ -8380,38 +8421,38 @@
     unsigned int __localBuffer = 0;
 
     if (__isSmallInteger(bufferOrInteger)) {
-        __useLocalBuffer = 1;
-        __buffer = (unsigned char *)&__localBuffer;
-        __bufferSize = __smallIntegerVal(bufferOrInteger);
-        if (__bufferSize > sizeof(INT))
-            __bufferSize = sizeof(INT);
+	__useLocalBuffer = 1;
+	__buffer = (unsigned char *)&__localBuffer;
+	__bufferSize = __smallIntegerVal(bufferOrInteger);
+	if (__bufferSize > sizeof(INT))
+	    __bufferSize = sizeof(INT);
     } else if (__isString(bufferOrInteger)) {
-        __buffer = __stringVal(bufferOrInteger);
-        __bufferSize = __stringSize(bufferOrInteger);
+	__buffer = __stringVal(bufferOrInteger);
+	__bufferSize = __stringSize(bufferOrInteger);
     } else if (__isByteArray(bufferOrInteger)) {
-        __buffer = __byteArrayVal(bufferOrInteger);
-        __bufferSize = __byteArraySize(bufferOrInteger);
+	__buffer = __byteArrayVal(bufferOrInteger);
+	__bufferSize = __byteArraySize(bufferOrInteger);
     } else {
-        goto error;
+	goto error;
     }
 
     if (P_RtlGenRandom == 0) {
-        HINSTANCE hAdvapi32 = LoadLibrary("advapi32.dll");
-        // console_printf("hAdvapi32: %x\n", hAdvapi32);
-        if (hAdvapi32) {
-            P_RtlGenRandom = (BOOL (__stdcall *)(PVOID , ULONG))
-                                GetProcAddress(hAdvapi32, "SystemFunction036");
-            // console_printf("P_RtlGenRandom: %x\n", P_RtlGenRandom);
-            if (P_RtlGenRandom == 0) {
-                goto error;
-            }
-        }
+	HINSTANCE hAdvapi32 = LoadLibrary("advapi32.dll");
+	// console_printf("hAdvapi32: %x\n", hAdvapi32);
+	if (hAdvapi32) {
+	    P_RtlGenRandom = (BOOL (__stdcall *)(PVOID , ULONG))
+				GetProcAddress(hAdvapi32, "SystemFunction036");
+	    // console_printf("P_RtlGenRandom: %x\n", P_RtlGenRandom);
+	    if (P_RtlGenRandom == 0) {
+		goto error;
+	    }
+	}
     }
     if ((*P_RtlGenRandom)(__buffer, __bufferSize)) {
-        if (__useLocalBuffer) {
-            RETURN(__mkSmallInteger(__localBuffer & _MAX_INT));
-        }
-        RETURN (bufferOrInteger);
+	if (__useLocalBuffer) {
+	    RETURN(__mkSmallInteger(__localBuffer & _MAX_INT));
+	}
+	RETURN (bufferOrInteger);
     }
 error: ;
 %}.
@@ -8433,15 +8474,15 @@
 
     if (__isStringLike(aStringOrSymbol)
      && __isStringLike(newValueString) ) {
-        if (SetEnvironmentVariable(__stringVal(aStringOrSymbol), __stringVal(newValueString)) != 0) {
-            RETURN(self);
-        }
+	if (SetEnvironmentVariable(__stringVal(aStringOrSymbol), __stringVal(newValueString)) != 0) {
+	    RETURN(self);
+	}
     }
 %}.
     self primitiveFailed
 
     "
-     OperatingSystem getEnvironment:'PATH'   
+     OperatingSystem getEnvironment:'PATH'
      OperatingSystem setEnvironment:'PATH' to:('c:\cygwin\bin;' , (OperatingSystem getEnvironment:'PATH'))
     "
 !
@@ -9755,22 +9796,22 @@
     if (__bothSmallInteger(y, m)
      && __bothSmallInteger(d, h)
      && __bothSmallInteger(min, s)) {
-        SYSTEMTIME sysTime;
-        FILETIME fileTime;
-
-        sysTime.wHour = __intVal(h);
-        sysTime.wMinute = __intVal(min);
-        sysTime.wSecond = __intVal(s);
-        sysTime.wMilliseconds = 0;
-
-        sysTime.wYear = __intVal(y);
-        sysTime.wMonth = __intVal(m);
-        sysTime.wDay = __intVal(d);
-
-        if (SystemTimeToFileTime(&sysTime, &fileTime) == 0)
-            goto error;
-
-        RETURN(FileTimeToOsTime(&fileTime));
+	SYSTEMTIME sysTime;
+	FILETIME fileTime;
+
+	sysTime.wHour = __intVal(h);
+	sysTime.wMinute = __intVal(min);
+	sysTime.wSecond = __intVal(s);
+	sysTime.wMilliseconds = 0;
+
+	sysTime.wYear = __intVal(y);
+	sysTime.wMonth = __intVal(m);
+	sysTime.wDay = __intVal(d);
+
+	if (SystemTimeToFileTime(&sysTime, &fileTime) == 0)
+	    goto error;
+
+	RETURN(FileTimeToOsTime(&fileTime));
     }
 error:;
 %}.
@@ -9793,30 +9834,30 @@
     if (__bothSmallInteger(y, m)
      && __bothSmallInteger(d, h)
      && __bothSmallInteger(min, s)) {
-        SYSTEMTIME sysTime;
-        FILETIME fileTime;
-
-        sysTime.wHour = __intVal(h);
-        sysTime.wMinute = __intVal(min);
-        sysTime.wSecond = __intVal(s);
-        sysTime.wMilliseconds = 0;
-
-        sysTime.wYear = __intVal(y);
-        sysTime.wMonth = __intVal(m);
-        sysTime.wDay = __intVal(d);
+	SYSTEMTIME sysTime;
+	FILETIME fileTime;
+
+	sysTime.wHour = __intVal(h);
+	sysTime.wMinute = __intVal(min);
+	sysTime.wSecond = __intVal(s);
+	sysTime.wMilliseconds = 0;
+
+	sysTime.wYear = __intVal(y);
+	sysTime.wMonth = __intVal(m);
+	sysTime.wDay = __intVal(d);
 
 #if 0
-        /* Sorry, but this function is not supported in Win2000
-           - we use LocalFileTimeToFileTime */
-        if (TzSpecificLocalTimeToSystemTime(0, &sysTime, &sysTime) == 0)
-            goto error;
-#endif
-        if (SystemTimeToFileTime(&sysTime, &fileTime) == 0)
-            goto error;
-        if (LocalFileTimeToFileTime(&fileTime, &fileTime) == 0)
-            goto error;
-
-        RETURN(FileTimeToOsTime(&fileTime));
+	/* Sorry, but this function is not supported in Win2000
+	   - we use LocalFileTimeToFileTime */
+	if (TzSpecificLocalTimeToSystemTime(0, &sysTime, &sysTime) == 0)
+	    goto error;
+#endif
+	if (SystemTimeToFileTime(&sysTime, &fileTime) == 0)
+	    goto error;
+	if (LocalFileTimeToFileTime(&fileTime, &fileTime) == 0)
+	    goto error;
+
+	RETURN(FileTimeToOsTime(&fileTime));
     }
 error:;
 %}.
@@ -9844,10 +9885,10 @@
     LONGLONG micros;
 
     if (! frequencyKnown) {
-        // get the high resolution counter's accuracy
-        QueryPerformanceFrequency(&ticksPerSecond);
-        frequencyKnown = 1;
-        divisor = ticksPerSecond / (LONGLONG)1000000;
+	// get the high resolution counter's accuracy
+	QueryPerformanceFrequency(&ticksPerSecond);
+	frequencyKnown = 1;
+	divisor = ticksPerSecond / (LONGLONG)1000000;
     }
 
     // what time is it?
@@ -9883,8 +9924,8 @@
      Use the millisecondTimeXXX:-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.
@@ -10047,43 +10088,43 @@
 
     /* try cache */
     {
-        OBJ lastSeconds, lastTimeInfo;
-
-        lastSeconds = @global(LastTimeInfoSeconds);
-        if (lastSeconds
-         && (__longIntVal(lastSeconds) == t)
-         && (@global(LastTimeInfoMilliseconds) == osMilliseconds)
-         && (@global(LastTimeInfoIsLocal) == isLocalTime)
-        ) {
-            lastTimeInfo = @global(LastTimeInfo);
-            if (lastTimeInfo != nil) {
-                RETURN (lastTimeInfo);
-            }
-        }
+	OBJ lastSeconds, lastTimeInfo;
+
+	lastSeconds = @global(LastTimeInfoSeconds);
+	if (lastSeconds
+	 && (__longIntVal(lastSeconds) == t)
+	 && (@global(LastTimeInfoMilliseconds) == osMilliseconds)
+	 && (@global(LastTimeInfoIsLocal) == isLocalTime)
+	) {
+	    lastTimeInfo = @global(LastTimeInfo);
+	    if (lastTimeInfo != nil) {
+		RETURN (lastTimeInfo);
+	    }
+	}
     }
 
     TimetToFileTime((time_t)t, &fileTime);
 
     if (isLocalTime == true) {
-        TIME_ZONE_INFORMATION tzInfo;
-        int tzState;
-        LONGLONG longTime;
-
-        FileTimeToLocalFileTime(&fileTime, &localFileTime);
-        FileTimeToSystemTime(&localFileTime, &sysTime);
-
-        longTime = ((LONGLONG)fileTime.dwHighDateTime << 32) + fileTime.dwLowDateTime;
-        longTime -= ((LONGLONG)localFileTime.dwHighDateTime << 32) + localFileTime.dwLowDateTime;
-        utcOffset = __mkSmallInteger((INT)(longTime / 10000000));
-
-        if ((tzState = GetTimeZoneInformation(&tzInfo)) < 0) {
-            reason = @symbol(getTimeZoneFailed);
-            goto error;
-        }
-        dstOffset = __mkSmallInteger((tzInfo.Bias + tzInfo.DaylightBias) * 60);
+	TIME_ZONE_INFORMATION tzInfo;
+	int tzState;
+	LONGLONG longTime;
+
+	FileTimeToLocalFileTime(&fileTime, &localFileTime);
+	FileTimeToSystemTime(&localFileTime, &sysTime);
+
+	longTime = ((LONGLONG)fileTime.dwHighDateTime << 32) + fileTime.dwLowDateTime;
+	longTime -= ((LONGLONG)localFileTime.dwHighDateTime << 32) + localFileTime.dwLowDateTime;
+	utcOffset = __mkSmallInteger((INT)(longTime / 10000000));
+
+	if ((tzState = GetTimeZoneInformation(&tzInfo)) < 0) {
+	    reason = @symbol(getTimeZoneFailed);
+	    goto error;
+	}
+	dstOffset = __mkSmallInteger((tzInfo.Bias + tzInfo.DaylightBias) * 60);
     } else {
-        FileTimeToSystemTime(&fileTime, &sysTime);
-        utcOffset = __mkSmallInteger(0);
+	FileTimeToSystemTime(&fileTime, &sysTime);
+	utcOffset = __mkSmallInteger(0);
     }
 
     hours = __mkSmallInteger(sysTime.wHour);
@@ -10098,22 +10139,22 @@
 error:;
 %}.
     year isNil ifTrue:[
-        ^ self primitiveFailed
+	^ self primitiveFailed
     ].
 
     info := self timeInfoClass new.
     info
-        year:year
-        month:month
-        day:day
-        hours:hours
-        minutes:minutes
-        seconds:seconds
-        milliseconds:osMilliseconds
-        utcOffset:utcOffset
-        dst:(utcOffset = dstOffset)
-        dayInYear:yDay
-        dayInWeek:weekDay.
+	year:year
+	month:month
+	day:day
+	hours:hours
+	minutes:minutes
+	seconds:seconds
+	milliseconds:osMilliseconds
+	utcOffset:utcOffset
+	dst:(utcOffset = dstOffset)
+	dayInYear:yDay
+	dayInWeek:weekDay.
 
     LastTimeInfo := info.
     LastTimeInfoSeconds := osSeconds.
@@ -10452,79 +10493,79 @@
     DWORD endStatus;
 
     if (__isExternalAddressLike(pidToWait) ) {
-        HANDLE __pidToWait = _HANDLEVal(pidToWait);
-        int t;
+	HANDLE __pidToWait = _HANDLEVal(pidToWait);
+	int t;
 
 #ifdef PROCESSDEBUG_CHILDPROCESSWAIT
-        console_printf("childProcessWait %x b %d\n",__pidToWait,blocking==true);
-#endif
-        t = (blocking==true) ? INFINITE : 0;
+	console_printf("childProcessWait %x b %d\n",__pidToWait,blocking==true);
+#endif
+	t = (blocking==true) ? INFINITE : 0;
 
 #ifdef DO_WRAP_CALLS
-        if (t == 0) {
-            /* no need for WRAP-call; does not block */
-            endStatus = WaitForSingleObject(__pidToWait, t);
-            if (endStatus < 0) {
-                __threadErrno = __WIN32_ERR(GetLastError());
-            }
-        } else {
-            do {
-                __threadErrno = 0;
-                endStatus = STX_API_CALL2( "WaitForSingleObject", WaitForSingleObject, __pidToWait, t);
-            } while ((endStatus < 0) && (__threadErrno == EINTR));
-        }
-#else
-        endStatus = WaitForSingleObject(__pidToWait, t);
-        if (endStatus < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        if ( endStatus == WAIT_TIMEOUT ) {
-            if (blocking==true)
-                status = @symbol(timeout);
-            else {
-                status = @symbol(continue);
+	if (t == 0) {
+	    /* no need for WRAP-call; does not block */
+	    endStatus = WaitForSingleObject(__pidToWait, t);
+	    if (endStatus < 0) {
+		__threadErrno = __WIN32_ERR(GetLastError());
+	    }
+	} else {
+	    do {
+		__threadErrno = 0;
+		endStatus = STX_API_CALL2( "WaitForSingleObject", WaitForSingleObject, __pidToWait, t);
+	    } while ((endStatus < 0) && (__threadErrno == EINTR));
+	}
+#else
+	endStatus = WaitForSingleObject(__pidToWait, t);
+	if (endStatus < 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
+#endif
+	if ( endStatus == WAIT_TIMEOUT ) {
+	    if (blocking==true)
+		status = @symbol(timeout);
+	    else {
+		status = @symbol(continue);
 #ifdef PROCESSDEBUG_CHILDPROCESSWAIT
-                console_printf("ret nil\n");
-#endif
-                RETURN(nil);
-            }
-        } else {
-            status = @symbol(exit);
+		console_printf("ret nil\n");
+#endif
+		RETURN(nil);
+	    }
+	} else {
+	    status = @symbol(exit);
 #ifdef PROCESSDEBUG_CHILDPROCESSWAIT
-            console_printf("exit\n");
-#endif
-            if (endStatus == WAIT_OBJECT_0) {
-                DWORD exitCode;
-
-                if (GetExitCodeProcess(__pidToWait, &exitCode)) {
+	    console_printf("exit\n");
+#endif
+	    if (endStatus == WAIT_OBJECT_0) {
+		DWORD exitCode;
+
+		if (GetExitCodeProcess(__pidToWait, &exitCode)) {
 #ifdef PROCESSDEBUG_CHILDPROCESSWAIT
-                    console_printf("exitCode: %d\n", exitCode);
-#endif
-                    if (exitCode == STILL_ACTIVE) {
-                        RETURN(nil);
-                    }
+		    console_printf("exitCode: %d\n", exitCode);
+#endif
+		    if (exitCode == STILL_ACTIVE) {
+			RETURN(nil);
+		    }
 #ifdef PROCESSDEBUG_CHILDPROCESSWAIT
-                    console_printf("exit %d\n", exitCode);
-#endif
-                    code = __mkSmallInteger(exitCode);
-                } else {
+		    console_printf("exit %d\n", exitCode);
+#endif
+		    code = __mkSmallInteger(exitCode);
+		} else {
 #ifdef PROCESSDEBUG_CHILDPROCESSWAIT
-                    console_printf("GetExitCodeProcess failed\n");
-#endif
-                    code = __mkSmallInteger(GetLastError());
-                }
-            } else {
-                code = __mkSmallInteger(-1);
-            }
-        }
-        core = false;
-        pid = pidToWait;
+		    console_printf("GetExitCodeProcess failed\n");
+#endif
+		    code = __mkSmallInteger(GetLastError());
+		}
+	    } else {
+		code = __mkSmallInteger(-1);
+	    }
+	}
+	core = false;
+	pid = pidToWait;
     }
 %}.
 
     (status isNil or:[pid isNil]) ifTrue:[
-        ^ self primitiveFailed
+	^ self primitiveFailed
     ].
 
 "/ Transcript show:'pid: '; show:pid; show:' status: '; show:status;
@@ -11731,8 +11772,8 @@
     "
 	VISTA:
 
-	Wer versucht unter Vista die Registy HKEY_PERFORMANCE_DATA abzufragen wird zunächst enttäuscht.
-	Die UAC UserAccessControl verhindern dies nämlich (selbs für den admin).
+	Wer versucht unter Vista die Registy HKEY_PERFORMANCE_DATA abzufragen wird zunchst enttuscht.
+	Die UAC UserAccessControl verhindern dies nmlich (selbs fr den admin).
 
 	Um dies zu umgehen:
 
@@ -14809,88 +14850,88 @@
     BOOL ok;
 
     if ((hFile == 0) || (hFile == INVALID_HANDLE_VALUE)) {
-        errSym = @symbol(errorNotOpen);
-        goto bad;
+	errSym = @symbol(errorNotOpen);
+	goto bad;
     }
     if (! __bothSmallInteger(count, firstIndex)) {
-        errSym = @symbol(badArgument);
-        goto bad;
+	errSym = @symbol(badArgument);
+	goto bad;
     }
     cntWanted = __smallIntegerVal(count);
     if (cntWanted <= 0) {
-        errSym = @symbol(badCount);
-        goto bad;
+	errSym = @symbol(badCount);
+	goto bad;
     }
     offs = __smallIntegerVal(firstIndex) - 1;
     if (offs < 0) {
-        errSym = @symbol(badOffset);
-        goto bad;
+	errSym = @symbol(badOffset);
+	goto bad;
     }
 
     bufferIsExternalBytes = __isExternalBytesLike(aByteBuffer);
     if (! bufferIsExternalBytes) {
-        if (__isByteArray(aByteBuffer)) {
-            bufferSize = __byteArraySize(aByteBuffer);
-        } else if (__isString(aByteBuffer)) {  // not isStringLike here !
-            bufferSize = __stringSize(aByteBuffer);
-        } else {
-            errSym = @symbol(badBuffer);
-            goto bad;
-        }
-        if (bufferSize < (cntWanted + offs)) {
-            errSym = @symbol(badBufferSize);
-            goto bad;
-        }
-        if (cntWanted <= sizeof(miniBuffer)) {
-            extPtr = miniBuffer;
-        } else {
-            extPtr = malloc(cntWanted);
-            mustFreeBuffer = 1;
-        }
+	if (__isByteArray(aByteBuffer)) {
+	    bufferSize = __byteArraySize(aByteBuffer);
+	} else if (__isString(aByteBuffer)) {  // not isStringLike here !
+	    bufferSize = __stringSize(aByteBuffer);
+	} else {
+	    errSym = @symbol(badBuffer);
+	    goto bad;
+	}
+	if (bufferSize < (cntWanted + offs)) {
+	    errSym = @symbol(badBufferSize);
+	    goto bad;
+	}
+	if (cntWanted <= sizeof(miniBuffer)) {
+	    extPtr = miniBuffer;
+	} else {
+	    extPtr = malloc(cntWanted);
+	    mustFreeBuffer = 1;
+	}
     } else {
-        OBJ sz;
-
-        extPtr = (char *)(__externalBytesAddress(aByteBuffer));
-        sz = __externalBytesSize(aByteBuffer);
-        if (! __isSmallInteger(sz)) {
-            errSym = @symbol(badBufferSize);
-            goto bad;
-        }
-        bufferSize = __smallIntegerVal(sz);
-        if (bufferSize < (cntWanted + offs)) {
-            errSym = @symbol(badBufferSize);
-            goto bad;
-        }
-        extPtr = extPtr + offs;
+	OBJ sz;
+
+	extPtr = (char *)(__externalBytesAddress(aByteBuffer));
+	sz = __externalBytesSize(aByteBuffer);
+	if (! __isSmallInteger(sz)) {
+	    errSym = @symbol(badBufferSize);
+	    goto bad;
+	}
+	bufferSize = __smallIntegerVal(sz);
+	if (bufferSize < (cntWanted + offs)) {
+	    errSym = @symbol(badBufferSize);
+	    goto bad;
+	}
+	extPtr = extPtr + offs;
     }
 
     do {
-        __threadErrno = 0;
-        ok = STX_API_NOINT_CALL5( "ReadFile", ReadFile, hFile, extPtr, cntWanted, &cntRead, 0 /* lpOverlapped */);
+	__threadErrno = 0;
+	ok = STX_API_NOINT_CALL5( "ReadFile", ReadFile, hFile, extPtr, cntWanted, &cntRead, 0 /* lpOverlapped */);
     } while(__threadErrno == EINTR);
 
     if (ok == TRUE) {
-        if (! bufferIsExternalBytes) {
-            /* copy over */
-            memcpy(__byteArrayVal(aByteBuffer)+offs, extPtr, cntRead);
-            if (mustFreeBuffer) {
-                free(extPtr);
-            }
-        }
-        RETURN (__mkSmallInteger(cntRead));
+	if (! bufferIsExternalBytes) {
+	    /* copy over */
+	    memcpy(__byteArrayVal(aByteBuffer)+offs, extPtr, cntRead);
+	    if (mustFreeBuffer) {
+		free(extPtr);
+	    }
+	}
+	RETURN (__mkSmallInteger(cntRead));
     }
     errorNumber = __mkSmallInteger( __WIN32_ERR(GetLastError()) );
 
 bad: ;
     if (mustFreeBuffer) {
-        free(extPtr);
+	free(extPtr);
     }
 %}.
 
     errorNumber isNil ifTrue:[
-        self error:'invalid argument(s): ', errSym.
+	self error:'invalid argument(s): ', errSym.
     ] ifFalse:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError
     ].
 
     "
@@ -15053,82 +15094,82 @@
     BOOL ok;
 
     if ((hFile == 0) || (hFile == INVALID_HANDLE_VALUE)) {
-        errSym = @symbol(errorNotOpen);
-        goto bad;
+	errSym = @symbol(errorNotOpen);
+	goto bad;
     }
     if (! __bothSmallInteger(count, firstIndex)) {
-        errSym = @symbol(badArgument);
-        goto bad;
+	errSym = @symbol(badArgument);
+	goto bad;
     }
     cntWanted = __smallIntegerVal(count);
     if (cntWanted <= 0) {
-        errSym = @symbol(badCount);
-        goto bad;
+	errSym = @symbol(badCount);
+	goto bad;
     }
     offs = __smallIntegerVal(firstIndex) - 1;
     if (offs < 0) {
-        errSym = @symbol(badOffset);
-        goto bad;
+	errSym = @symbol(badOffset);
+	goto bad;
     }
 
     bufferIsExternalBytes = __isExternalBytesLike(aByteBuffer);
     if (! bufferIsExternalBytes) {
-        if (__isByteArray(aByteBuffer)) {
-            bufferSize = __byteArraySize(aByteBuffer);
-        } else if (__isStringLike(aByteBuffer)) {
-            bufferSize = __stringSize(aByteBuffer);
-        } else {
-            errSym = @symbol(badBuffer);
-            goto bad;
-        }
-        if (bufferSize < (cntWanted + offs)) {
-            errSym = @symbol(badBufferSize);
-            goto bad;
-        }
-        if (cntWanted <= sizeof(miniBuffer)) {
-            extPtr = miniBuffer;
-        } else {
-            extPtr = malloc(cntWanted);
-            mustFreeBuffer = 1;
-        }
-        memcpy(extPtr, __byteArrayVal(aByteBuffer)+offs, cntWanted);
+	if (__isByteArray(aByteBuffer)) {
+	    bufferSize = __byteArraySize(aByteBuffer);
+	} else if (__isStringLike(aByteBuffer)) {
+	    bufferSize = __stringSize(aByteBuffer);
+	} else {
+	    errSym = @symbol(badBuffer);
+	    goto bad;
+	}
+	if (bufferSize < (cntWanted + offs)) {
+	    errSym = @symbol(badBufferSize);
+	    goto bad;
+	}
+	if (cntWanted <= sizeof(miniBuffer)) {
+	    extPtr = miniBuffer;
+	} else {
+	    extPtr = malloc(cntWanted);
+	    mustFreeBuffer = 1;
+	}
+	memcpy(extPtr, __byteArrayVal(aByteBuffer)+offs, cntWanted);
     } else {
-        extPtr = (char *)(__externalBytesAddress(aByteBuffer));
-        bufferSize = __externalBytesSize(aByteBuffer);
-        if (! __isSmallInteger(bufferSize)) {
-            errSym = @symbol(badBufferSize);
-            goto bad;
-        }
-        bufferSize = __smallIntegerVal(bufferSize);
-        if (bufferSize < (cntWanted + offs)) {
-            errSym = @symbol(badBufferSize);
-            goto bad;
-        }
-        extPtr = extPtr + offs;
+	extPtr = (char *)(__externalBytesAddress(aByteBuffer));
+	bufferSize = __externalBytesSize(aByteBuffer);
+	if (! __isSmallInteger(bufferSize)) {
+	    errSym = @symbol(badBufferSize);
+	    goto bad;
+	}
+	bufferSize = __smallIntegerVal(bufferSize);
+	if (bufferSize < (cntWanted + offs)) {
+	    errSym = @symbol(badBufferSize);
+	    goto bad;
+	}
+	extPtr = extPtr + offs;
     }
 
     do {
-        __threadErrno = 0;
-        ok = STX_API_NOINT_CALL5( "WriteFile", WriteFile, hFile, extPtr, cntWanted, &cntWritten, 0 /* lpOverlapped */);
+	__threadErrno = 0;
+	ok = STX_API_NOINT_CALL5( "WriteFile", WriteFile, hFile, extPtr, cntWanted, &cntWritten, 0 /* lpOverlapped */);
     } while(__threadErrno == EINTR);
 
     if (ok == TRUE) {
-        if (mustFreeBuffer) {
-            free(extPtr);
-        }
-        RETURN (__mkSmallInteger(cntWritten));
+	if (mustFreeBuffer) {
+	    free(extPtr);
+	}
+	RETURN (__mkSmallInteger(cntWritten));
     }
     errorNumber = __mkSmallInteger( __WIN32_ERR(GetLastError()) );
 
 bad: ;
     if (mustFreeBuffer) {
-        free(extPtr);
+	free(extPtr);
     }
 %}.
     errorNumber isNil ifTrue:[
-        self error:'invalid argument(s): ', errSym.
+	self error:'invalid argument(s): ', errSym.
     ] ifFalse:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError
     ].
 
     "
@@ -15586,10 +15627,10 @@
     type := OperatingSystem socketTypeCodeOf:typeArg.
     proto := self protocolCodeOf:protoArg.
     serviceNameArg notNil ifTrue:[
-        serviceName := serviceNameArg printString.      "convert integer port numbers"
-        serviceNameArg isInteger ifTrue:[
-            port := serviceNameArg.
-        ].
+	serviceName := serviceNameArg printString.      "convert integer port numbers"
+	serviceNameArg isInteger ifTrue:[
+	    port := serviceNameArg.
+	].
     ]. "ifFalse:[serviceName := nil]"
 
 %{ /* STACK:32000 */
@@ -15598,24 +15639,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 exitPrim;
+	error = @symbol(badArgument1);
+	goto exitPrim;
     }
     if (serviceName == nil) {
-        __serviceName = 0;
+	__serviceName = 0;
     } else if (__isStringLike(serviceName)) {
-        __serviceName = __stringVal(serviceName);
+	__serviceName = __stringVal(serviceName);
     } else {
-        error = @symbol(badArgument2);
-        goto exitPrim;
+	error = @symbol(badArgument2);
+	goto exitPrim;
     }
     if (__hostName == 0 && __serviceName == 0) {
-        error = @symbol(badArgument);
-        goto exitPrim;
+	error = @symbol(badArgument);
+	goto exitPrim;
     }
 
 {
@@ -15628,121 +15669,121 @@
 
     memset(&hints, 0, sizeof(hints));
     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);
 
     do {
-        /* must refetch in loop */
-        if (hostName == nil) {
-            __hostName = 0;
-        } else if (__isStringLike(hostName)) {
-            __hostName = __stringVal(hostName);
-        }
-        if (serviceName == nil) {
-            __serviceName = 0;
-        } else if (__isStringLike(serviceName)) {
-            __serviceName = __stringVal(serviceName);
-        }
+	/* must refetch in loop */
+	if (hostName == nil) {
+	    __hostName = 0;
+	} else if (__isStringLike(hostName)) {
+	    __hostName = __stringVal(hostName);
+	}
+	if (serviceName == nil) {
+	    __serviceName = 0;
+	} else if (__isStringLike(serviceName)) {
+	    __serviceName = __stringVal(serviceName);
+	}
 
 # ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            res = STX_WSA_NOINT_CALL4( "getaddrinfo", getaddrinfo, __hostName, __serviceName, &hints, &info);
-        } while ((res < 0) && (__threadErrno == EINTR));
+	do {
+	    __threadErrno = 0;
+	    res = STX_WSA_NOINT_CALL4( "getaddrinfo", getaddrinfo, __hostName, __serviceName, &hints, &info);
+	} while ((res < 0) && (__threadErrno == EINTR));
 # else
-        __BEGIN_INTERRUPTABLE__
-        ret = getaddrinfo(__hostName, __serviceName, &hints, &info);
-        __END_INTERRUPTABLE__
+	__BEGIN_INTERRUPTABLE__
+	ret = getaddrinfo(__hostName, __serviceName, &hints, &info);
+	__END_INTERRUPTABLE__
 # endif
     } 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;
-        case EAI_ADDRFAMILY :
-            error = @symbol(unknownHostForProtocol);
-            break;
-        case EAI_NODATA:
-            error = @symbol(noAddress);
-            break;
-        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;
+	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;
+	case EAI_ADDRFAMILY :
+	    error = @symbol(unknownHostForProtocol);
+	    break;
+	case EAI_NODATA:
+	    error = @symbol(noAddress);
+	    break;
+	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:
@@ -15759,148 +15800,148 @@
     int i;
 
     if (__isSmallInteger(port)) {
-        __port = htons(__smallIntegerVal(port));
+	__port = htons(__smallIntegerVal(port));
     } else if (__serviceName) {
-        struct servent *sp;
-        char *__proto = 0;
-
-        if (__isStringLike(protoArg))
-            __proto = __stringVal(protoArg);
-
-        sp = getservbyname(__serviceName, __proto);
-        if (sp == NULL) {
-            __port = atoi(__serviceName);
-            if (__port <= 0) {
-                errorString = @symbol(unknownService);
-                error = __mkSmallInteger(-3);
-                goto err;
-            }
-            __port = htons(__port);
-        } else
-            __port = sp->s_port;
+	struct servent *sp;
+	char *__proto = 0;
+
+	if (__isStringLike(protoArg))
+	    __proto = __stringVal(protoArg);
+
+	sp = getservbyname(__serviceName, __proto);
+	if (sp == NULL) {
+	    __port = atoi(__serviceName);
+	    if (__port <= 0) {
+		errorString = @symbol(unknownService);
+		error = __mkSmallInteger(-3);
+		goto err;
+	    }
+	    __port = htons(__port);
+	} else
+	    __port = sp->s_port;
     }
 
     if (__hostName) {
 #  ifdef USE_H_ERRNO
-        do {
-            /* must refetch in loop */
-            if (hostName == nil) {
-                __hostName = 0;
-            } else if (__isStringLike(hostName)) {
-                __hostName = __stringVal(hostName);
-            }
+	do {
+	    /* must refetch in loop */
+	    if (hostName == nil) {
+		__hostName = 0;
+	    } else if (__isStringLike(hostName)) {
+		__hostName = __stringVal(hostName);
+	    }
 # ifdef DO_WRAP_CALLS
-            hp = STX_WSA_NOINT_CALL1("gethostbyname", gethostbyname, __hostName);
-            if ((INT)hp < 0) hp = NULL;
+	    hp = STX_WSA_NOINT_CALL1("gethostbyname", gethostbyname, __hostName);
+	    if ((INT)hp < 0) hp = NULL;
 # else
-            /* __BEGIN_INTERRUPTABLE__ is dangerous, because gethostbyname
-             * uses a static data area
-             */
-            __BEGIN_INTERRUPTABLE__
-            hp = gethostbyname(__hostName);
-            __END_INTERRUPTABLE__
-#endif
-        } while ((hp == NULL)
-                  && (
-                        (h_errno == TRY_AGAIN)
-                      || errno == EINTR
+	    /* __BEGIN_INTERRUPTABLE__ is dangerous, because gethostbyname
+	     * uses a static data area
+	     */
+	    __BEGIN_INTERRUPTABLE__
+	    hp = gethostbyname(__hostName);
+	    __END_INTERRUPTABLE__
+#endif
+	} 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:;
@@ -15912,58 +15953,58 @@
 exitPrim:;
 %}.
     error notNil ifTrue:[
-        |request|
-        request := SocketAddressInfo new
-            domain:domainArg;
-            type:typeArg;
-            protocol:protoArg;
-            canonicalName:hostName;
-            serviceName:serviceName.
-        ^ (HostNameLookupError new
-                parameter:error;
-                messageText:' - ', (errorString ? error printString);
-                request:request) raiseRequest.
+	|request|
+	request := SocketAddressInfo new
+	    domain:domainArg;
+	    type:typeArg;
+	    protocol:protoArg;
+	    canonicalName:hostName;
+	    serviceName:serviceName.
+	^ (HostNameLookupError new
+		parameter:error;
+		messageText:' - ', (errorString ? error printString);
+		request:request) raiseRequest.
     ].
     1 to:result size do:[:i |
-        |entry dom info|
-
-        info := SocketAddressInfo new.
-        entry := result at:i.
-        info flags:(entry at:1).
-        info domain:(dom := OperatingSystem domainSymbolOf:(entry at:2)).
-        info type:(OperatingSystem socketTypeSymbolOf:(entry at:3)).
-        info protocol:(self protocolSymbolOf:(entry at:4)).
-        info socketAddress:((SocketAddress newDomain:dom) fromBytes:(entry at:5)).
-        info canonicalName:(entry at:6).
-        result at:i put:info
+	|entry dom info|
+
+	info := SocketAddressInfo new.
+	entry := result at:i.
+	info flags:(entry at:1).
+	info domain:(dom := OperatingSystem domainSymbolOf:(entry at:2)).
+	info type:(OperatingSystem socketTypeSymbolOf:(entry at:3)).
+	info protocol:(self protocolSymbolOf:(entry at:4)).
+	info socketAddress:((SocketAddress newDomain:dom) fromBytes:(entry at:5)).
+	info 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:'localhost' serviceName:10
-            domain:#inet type:#stream protocol:#tcp flags:nil
+	    domain:#inet type:#stream protocol:#tcp flags:nil
      self getAddressInfo:'localhost' serviceName:'10'
-            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:'smc1' serviceName:nil
-            domain:nil type:nil protocol:nil flags:nil
+	    domain:nil type:nil protocol:nil flags:nil
     "
 !
 
@@ -16252,17 +16293,18 @@
 !Win32OperatingSystem class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Win32OperatingSystem.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: Win32OperatingSystem.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/Win32OperatingSystem.st,v 1.401 2010/04/06 08:17:14 stefan Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/Win32OperatingSystem.st,v 1.403 2010/04/30 13:52:43 ca Exp §'
 !
 
 version_SVN
-    ^ '$Id: Win32OperatingSystem.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: Win32OperatingSystem.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
 
 Win32OperatingSystem initialize!
 Win32OperatingSystem::PerformanceData initialize!
 Win32OperatingSystem::RegistryEntry initialize!
+
--- a/abbrev.stc	Thu Apr 29 16:55:35 2010 +0100
+++ b/abbrev.stc	Tue May 04 12:50:05 2010 +0100
@@ -368,7 +368,7 @@
 ImmutableArray ImmutableArray stx:libbasic 'System-Compiler-Support' 0
 ImmutableByteArray ImmutableByteArray stx:libbasic 'System-Compiler-Support' 0
 ImmutableString ImmutableString stx:libbasic 'System-Compiler-Support' 0
-SandboxedMethod SandboxedMethod stx:libbasic 'Kernel-Methods' 0
 PrototypeLookupAlgorithm PrototypeLookupAlgorithm stx:libbasic 'Kernel-Classes' 0
 Lookup Lookup stx:libbasic 'Kernel-Classes' 0
 BuiltinLookup BuiltinLookup stx:libbasic 'Kernel-Classes' 0
+
--- a/bc.mak	Thu Apr 29 16:55:35 2010 +0100
+++ b/bc.mak	Tue May 04 12:50:05 2010 +0100
@@ -1,4 +1,4 @@
-# $Header$
+# $Header: /cvs/stx/stx/libbasic/bc.mak,v 1.166 2010/04/27 08:10:26 stefan Exp $
 #
 # DO NOT EDIT
 # automagically generated from the projectDefinition: stx_libbasic.
@@ -83,6 +83,7 @@
 $(OUTDIR)MiniInspector.$(O) MiniInspector.$(H): MiniInspector.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)NameSpace.$(O) NameSpace.$(H): NameSpace.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)OSErrorHolder.$(O) OSErrorHolder.$(H): OSErrorHolder.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)OSProcess.$(O) OSProcess.$(H): OSProcess.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ObjectMemory.$(O) ObjectMemory.$(H): ObjectMemory.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PackageId.$(O) PackageId.$(H): PackageId.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PluginSupport.$(O) PluginSupport.$(H): PluginSupport.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -339,6 +340,15 @@
 $(OUTDIR)WindowsDesktop.$(O) WindowsDesktop.$(H): WindowsDesktop.st $(STCHDR)
 $(OUTDIR)XDGDesktop.$(O) XDGDesktop.$(H): XDGDesktop.st $(STCHDR)
 $(OUTDIR)CmdLineOptionError.$(O) CmdLineOptionError.$(H): CmdLineOptionError.st $(STCHDR)
+$(OUTDIR)Win32Process.$(O) Win32Process.$(H): Win32Process.st $(STCHDR)
+$(OUTDIR)PCFilename.$(O) PCFilename.$(H): PCFilename.st $(STCHDR)
+$(OUTDIR)CharacterEncoderImplementations__MS_Baltic.$(O) CharacterEncoderImplementations__MS_Baltic.$(H): CharacterEncoderImplementations__MS_Baltic.st $(STCHDR)
+$(OUTDIR)CharacterEncoderImplementations__MS_Cyrillic.$(O) CharacterEncoderImplementations__MS_Cyrillic.$(H): CharacterEncoderImplementations__MS_Cyrillic.st $(STCHDR)
+$(OUTDIR)CharacterEncoderImplementations__MS_Greek.$(O) CharacterEncoderImplementations__MS_Greek.$(H): CharacterEncoderImplementations__MS_Greek.st $(STCHDR)
+$(OUTDIR)Win32Handle.$(O) Win32Handle.$(H): Win32Handle.st $(STCHDR)
+$(OUTDIR)Win32FILEHandle.$(O) Win32FILEHandle.$(H): Win32FILEHandle.st $(STCHDR)
+$(OUTDIR)Win32Constants.$(O) Win32Constants.$(H): Win32Constants.st $(STCHDR)
+$(OUTDIR)Win32OperatingSystem.$(O) Win32OperatingSystem.$(H): Win32OperatingSystem.st $(STCHDR)
 $(OUTDIR)GNOMEDesktop.$(O) GNOMEDesktop.$(H): GNOMEDesktop.st $(STCHDR)
 $(OUTDIR)SandboxedMethod.$(O) SandboxedMethod.$(H): SandboxedMethod.st $(STCHDR)
 $(OUTDIR)Win32Process.$(O) Win32Process.$(H): Win32Process.st $(STCHDR)
@@ -352,3 +362,4 @@
 $(OUTDIR)Win32OperatingSystem.$(O) Win32OperatingSystem.$(H): Win32OperatingSystem.st $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
+
--- a/libInit.cc	Thu Apr 29 16:55:35 2010 +0100
+++ b/libInit.cc	Tue May 04 12:50:05 2010 +0100
@@ -1,5 +1,5 @@
 /*
- * $Header$
+ * $Header: /cvs/stx/stx/libbasic/libInit.cc,v 1.158 2010/04/27 08:10:28 stefan Exp $
  *
  * DO NOT EDIT
  * automagically generated from the projectDefinition: stx_libbasic.
@@ -57,6 +57,7 @@
 _MiniInspector_Init(pass,__pRT__,snd);
 _NameSpace_Init(pass,__pRT__,snd);
 _OSErrorHolder_Init(pass,__pRT__,snd);
+_OSProcess_Init(pass,__pRT__,snd);
 _ObjectMemory_Init(pass,__pRT__,snd);
 _PackageId_Init(pass,__pRT__,snd);
 _PluginSupport_Init(pass,__pRT__,snd);
@@ -313,7 +314,6 @@
 _XDGDesktop_Init(pass,__pRT__,snd);
 _CmdLineOptionError_Init(pass,__pRT__,snd);
 _GNOMEDesktop_Init(pass,__pRT__,snd);
-_SandboxedMethod_Init(pass,__pRT__,snd);
 #ifdef UNIX
 _UnixFileDescriptorHandle_Init(pass,__pRT__,snd);
 _UnixFileHandle_Init(pass,__pRT__,snd);
@@ -334,3 +334,4 @@
 
 __END_PACKAGE__();
 }
+
--- a/libbasic.rc	Thu Apr 29 16:55:35 2010 +0100
+++ b/libbasic.rc	Tue May 04 12:50:05 2010 +0100
@@ -3,8 +3,8 @@
 // automagically generated from the projectDefinition: stx_libbasic.
 //
 VS_VERSION_INFO VERSIONINFO
-  FILEVERSION     5,4,10514,10514
-  PRODUCTVERSION  5,4,6,2
+  FILEVERSION     6,1,1,73
+  PRODUCTVERSION  6,1,1,1
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
   FILEFLAGS       VS_FF_PRERELEASE | VS_FF_SPECIALBUILD
   FILEOS          VOS_NT_WINDOWS32
@@ -18,12 +18,12 @@
     BEGIN
       VALUE "CompanyName", "eXept Software AG\0"
       VALUE "FileDescription", "Smalltalk/X Basic Classes (LIB)\0"
-      VALUE "FileVersion", "5.4.10514.10514\0"
+      VALUE "FileVersion", "6.1.1.73\0"
       VALUE "InternalName", "stx:libbasic\0"
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2009\nCopyright eXept Software AG 1998-2009\0"
       VALUE "ProductName", "Smalltalk/X\0"
-      VALUE "ProductVersion", "5.4.6.2\0"
-      VALUE "ProductDate", "Mon, 26 Apr 2010 17:32:14 GMT\0"
+      VALUE "ProductVersion", "6.1.1.1\0"
+      VALUE "ProductDate", "Tue, 27 Apr 2010 08:10:07 GMT\0"
     END
 
   END
@@ -33,3 +33,4 @@
     VALUE "Translation", 0x409, 0x4E4 // U.S. English, Windows Multilingual
   END
 END
+
--- a/stx_libbasic.st	Thu Apr 29 16:55:35 2010 +0100
+++ b/stx_libbasic.st	Tue May 04 12:50:05 2010 +0100
@@ -49,7 +49,7 @@
 
     ^ #(
         #'stx:goodies/sunit'    "TestResource - referenced by ProjectDefinition class>>additionalClassAttributesFor: "
-        #'stx:libsvn'    "SVN::InfoCommand - referenced by ProjectDefinition class>>svnRevision "
+        #'stx:libsvn'           "SVN::InfoCommand - referenced by ProjectDefinition class>>svnRevision "
         #'stx:goodies'    "Complex - referenced by Number>>asComplex "
         #'stx:goodies/simpleServices'    "STXScriptingServer - referenced by StandaloneStartup class>>setupSmalltalkFromArguments: "
         #'stx:goodies/soap/xe'    "SOAP::XePName - referenced by Date class>>sprayTypeName "
@@ -487,9 +487,9 @@
         ImmutableArray
         ImmutableByteArray
         ImmutableString
-        SandboxedMethod
         PrototypeLookupAlgorithm
         Lookup
+        OSProcess
         BuiltinLookup
     )
 !
@@ -530,19 +530,20 @@
     "Return a SVN revision number of myself.
      This number is updated after a commit"
 
-    ^ "$SVN-Revision:"'10514M'"$"
+    ^ "$SVN-Revision:"'10518M'"$"
 ! !
 
 !stx_libbasic class methodsFor:'documentation'!
 
 version
-    ^ '$Id: stx_libbasic.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: stx_libbasic.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 !
 
 version_CVS
-    ^ 'Header: /cvs/stx/stx/libbasic/stx_libbasic.st,v 1.72 2010/04/07 16:23:10 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libbasic/stx_libbasic.st,v 1.74 2010/04/27 08:10:31 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: stx_libbasic.st 10517 2010-04-26 18:26:38Z vranyj1 $'
+    ^ '$Id: stx_libbasic.st 10520 2010-05-04 11:50:05Z vranyj1 $'
 ! !
+