Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Sun, 09 Oct 2016 21:28:18 +0100
branchjv
changeset 20579 9add81aadb7a
parent 20578 39641ba8d6e0 (current diff)
parent 20566 b43ea3fc00be (diff)
child 20580 bb4e5c4f84ef
Merge
ApplicationDefinition.st
Array.st
Behavior.st
Block.st
ByteArray.st
Class.st
ClassBuilder.st
ClassDescription.st
CompiledCode.st
ExecutableFunction.st
ExternalFunction.st
ExternalLibraryFunction.st
Filename.st
ImmutableArray.st
ImmutableByteArray.st
ImmutableString.st
Method.st
MethodWithBreakpoints.st
MiniLogger.st
Object.st
PCFilename.st
ProjectDefinition.st
Smalltalk.st
StandaloneStartup.st
String.st
SystemChangeNotifier.st
Win32OperatingSystem.st
--- a/ApplicationDefinition.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/ApplicationDefinition.st	Sun Oct 09 21:28:18 2016 +0100
@@ -562,7 +562,8 @@
 !
 
 startupClassName
-    "The name of the class which provides the entry point for the application."
+    "return he name of the class which provides the entry point for the application;
+     a fully specified symbol or string."
 
     self subclassResponsibility
 
@@ -906,6 +907,7 @@
         at: 'APPLICATION' put: (self applicationName);
         at: 'NSI_FILENAME' put: self nsiFilename ;
         at: 'PRODUCT_NAME' put: (self productName);
+        at: 'PRODUCT_FILENAME' put: (self productFilename);
         at: 'CONSOLE_APPLICATION' put: (self applicationNameConsole);
         at: 'NOCONSOLE_APPLICATION' put: (self applicationNameNoConsole);
         at: 'NOCONSOLE_LOGFILE' put:(self logFilenameNoConsole);
@@ -998,13 +1000,14 @@
     "generate (unix) copy commands to generate a directory holding the dmg prototype image directory.
      This is used to generate a macOS deployable package"
 
-    |genLine product dmgVolume dmgDir appDir contentsDir macOSDir resourcesDir dirsMade|
+    |genLine product productFile dmgVolume dmgDir appDir contentsDir macOSDir resourcesDir dirsMade|
 
     product := self productName.
-
-    dmgVolume := product,'.dmg'.
-    dmgDir := product,'_dmg'.
-    appDir := dmgDir,'/',product,'.app'.
+    productFile := self productFilename.
+
+    dmgVolume := productFile,'.dmg'.
+    dmgDir := productFile,'_dmg'.
+    appDir := dmgDir,'/',productFile,'.app'.
     contentsDir := appDir,'/Contents'.
     macOSDir := contentsDir,'/MacOS'.
     resourcesDir := contentsDir,'/Resources'.
@@ -1033,7 +1036,7 @@
         s tab; nextPutLine:('@-mkdir "%1"' bindWith:appDir).  dirsMade add:appDir.
         s tab; nextPutLine:('@-mkdir "%1"' bindWith:contentsDir).  dirsMade add:contentsDir.
         s tab; nextPutLine:('@-mkdir "%1"' bindWith:macOSDir).  dirsMade add:macOSDir.
-        s tab; nextPutLine:('cp "',self applicationName,'" "',macOSDir,'/',product,'"').
+        s tab; nextPutLine:('cp "',self applicationName,'" "',macOSDir,'/',productFile,'"').
         self commonFilesToInstall_unix do:[:eachPair | genLine value:s value:'MacOS' value:eachPair].
         self additionalFilesToInstall_unix do:[:eachPair | genLine value:s value:'MacOS' value:eachPair].
     ].
@@ -1857,13 +1860,13 @@
 !!if defined(USEMINGW64)
 
 setup: $(PROJECT) postBuildCleanup %(NSI_FILENAME) 
-        $(MAKENSIS) /DOBJ_DIR=objmingw /DSETUP_NAME=%(PRODUCT_NAME)Setup64 %(NSI_FILENAME)
+        $(MAKENSIS) /DOBJ_DIR=objmingw /DSETUP_NAME=%(PRODUCT_FILENAME)Setup64 %(NSI_FILENAME)
         %(ADDITIONAL_POSTNSISRULES64)
 
 !!else
 
 setup: $(PROJECT) postBuildCleanup %(NSI_FILENAME)
-        $(MAKENSIS) /DOBJ_DIR=objbc /DSETUP_NAME=%(PRODUCT_NAME)Setup %(NSI_FILENAME)
+        $(MAKENSIS) /DOBJ_DIR=objbc /DSETUP_NAME=%(PRODUCT_FILENAME)Setup %(NSI_FILENAME)
         %(ADDITIONAL_POSTNSISRULES)
 
 !!endif
@@ -2501,13 +2504,13 @@
 #
 # for mac, a dmg is generated
 #
-setup_macosx:   "%(PRODUCT_NAME)_dmg"
-        -rm "%(PRODUCT_NAME).dmg"
-        hdiutil create -fs HFSX -layout SPUD "%(PRODUCT_NAME).dmg" -srcfolder "%(PRODUCT_NAME)_dmg" -format UDZO -volname "%(PRODUCT_NAME)" -quiet
-
-app: "%(PRODUCT_NAME)_dmg"
-
-"%(PRODUCT_NAME)_dmg": $(SUBPROJECT_LIBS) $(REQUIRED_SUPPORT_DIRS) 
+setup_macosx:   "%(PRODUCT_FILENAME)_dmg"
+        -rm "%(PRODUCT_FILENAME).dmg"
+        hdiutil create -fs HFSX -layout SPUD "%(PRODUCT_FILENAME).dmg" -srcfolder "%(PRODUCT_FILENAME)_dmg" -format UDZO -volname "%(PRODUCT_NAME)" -quiet
+
+app: "%(PRODUCT_FILENAME)_dmg"
+
+"%(PRODUCT_FILENAME)_dmg": $(SUBPROJECT_LIBS) $(REQUIRED_SUPPORT_DIRS) 
 %(DMG_IMAGE_SETUP)
 
 SOURCEFILES: %(APPLICATION)_SOURCES \
@@ -2930,7 +2933,7 @@
   WriteRegStr ${PRODUCT_UNINST_ROOT_KEY} "${PRODUCT_UNINST_KEY}" "Publisher" "${PRODUCT_PUBLISHER}"
 SectionEnd
 
-LangString appOpen ${LANG_GERMAN}  "Mit %(PRODUCT_NAME) öffnen"
+LangString appOpen ${LANG_GERMAN}  "Mit %(PRODUCT_NAME) ffnen"
 LangString appOpen ${LANG_ENGLISH} "Open with %(PRODUCT_NAME)"
 
 LangString DESC_Section1 ${LANG_ENGLISH} "Program components of %(PRODUCT_NAME)"
@@ -2964,7 +2967,7 @@
 
 Function un.onInit
 !!insertmacro MUI_UNGETLANGUAGE
-  MessageBox MB_ICONQUESTION|MB_YESNO|MB_DEFBUTTON2 "Möchten Sie %(PRODUCT_NAME) und alle seine Komponenten deinstallieren?" IDYES +2
+  MessageBox MB_ICONQUESTION|MB_YESNO|MB_DEFBUTTON2 "Mchten Sie %(PRODUCT_NAME) und alle seine Komponenten deinstallieren?" IDYES +2
   Abort
 FunctionEnd
 
--- a/Array.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/Array.st	Sun Oct 09 21:28:18 2016 +0100
@@ -510,6 +510,7 @@
 beImmutable
     "make myself write-protected"
 
+    super beImmutable.
     self changeClassTo:ImmutableArray
 
     "Created: / 07-06-2012 / 11:06:33 / cg"
@@ -1900,10 +1901,10 @@
      receiver refers to aLiteral (i.e. a deep search)"
 
     self do:[:el |
-	el == aLiteral ifTrue:[^true].
-	(el class == Array or:[el class == ImmutableArray]) ifTrue:[
-	    (el refersToLiteral: aLiteral) ifTrue: [^true]
-	]
+        el == aLiteral ifTrue:[^true].
+        el isArray ifTrue:[
+            (el refersToLiteral: aLiteral) ifTrue: [^true]
+        ]
     ].
     ^ false
 
@@ -1921,10 +1922,10 @@
      receiver is symbolic and matches aMatchPattern (i.e. a deep search)"
 
     self do:[ :el |
-	(el isSymbol and:[ aMatchPattern match: el]) ifTrue:[^true].
-	(el class == Array or:[el class == ImmutableArray]) ifTrue:[
-	    (el refersToLiteralMatching: aMatchPattern) ifTrue: [^true]
-	]
+        (el isSymbol and:[ aMatchPattern match: el]) ifTrue:[^true].
+        el isArray ifTrue:[
+            (el refersToLiteralMatching: aMatchPattern) ifTrue: [^true]
+        ]
     ].
     ^ false
 
--- a/Behavior.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/Behavior.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -1425,7 +1423,6 @@
 ! !
 
 
-
 !Behavior methodsFor:'RefactoringBrowser'!
 
 realClass
@@ -1443,30 +1440,30 @@
     |oldMethod ns nsName selector newLookupObject|
 
     (newSelector isMemberOf:Symbol) ifFalse:[
-	self error:'invalid selector'.
+        self error:'invalid selector'.
     ].
 
     ns := newMethod nameSpace.
     (ns notNil and:[(nsName := ns name) ~= self programmingLanguage defaultSelectorNameSpacePrefix]) ifTrue:[
-	selector := (':' , nsName , '::' , newSelector) asSymbol.
-	newLookupObject := Smalltalk at: #NamespaceAwareLookup. "/ so it can be nilled to disable that feature
+        selector := (':' , nsName , '::' , newSelector) asSymbol.
+        newLookupObject := Smalltalk at: #NamespaceAwareLookup. "/ so it can be nilled to disable that feature
     ] ifFalse:[
-	selector := newSelector
+        selector := newSelector
     ].
 
     "/ Q (cg): isn't that something that the caller should decide?
     oldMethod := self compiledMethodAt:selector.
     oldMethod notNil ifTrue:[
-	newMethod restricted:(oldMethod isRestricted).
-	newMethod setPrivacy:(oldMethod privacy) flushCaches:false.
+        newMethod restricted:(oldMethod isRestricted).
+        newMethod setPrivacy:(oldMethod privacy) flushCaches:false.
     ].
 
     (self primAddSelector:selector withMethod:newMethod) ifFalse:[^ false].
 
     newLookupObject notNil ifTrue:[
-	lookupObject ~= newLookupObject ifTrue:[
-	    self lookupObject: newLookupObject
-	]
+        lookupObject ~= newLookupObject ifTrue:[
+            self lookupObject: newLookupObject
+        ]
     ].
 
     "
@@ -1476,12 +1473,12 @@
     "
 "
     problem: this is slower; since looking for all subclasses is (currently)
-	     a bit slow :-(
-	     We need the hasSubclasses-info bit in Behavior; now
+             a bit slow :-(
+             We need the hasSubclasses-info bit in Behavior; now
 
     self withAllSubclassesDo:[:aClass |
-	ObjectMemory flushInlineCachesFor:aClass withArgs:nargs.
-	ObjectMemory flushMethodCacheFor:aClass
+        ObjectMemory flushInlineCachesFor:aClass withArgs:nargs.
+        ObjectMemory flushMethodCacheFor:aClass
     ].
 "
 
@@ -1492,6 +1489,12 @@
     self changed:#methodDictionary with:(Array with:selector with:oldMethod).
 
     "/
+    "/ pass the class AND selector AND the old method as changeArg
+    "/ - this allows for watchers to depend on a non-metaclass only, watching both sides.
+    "/
+    self theNonMetaclass changed:#classesMethodDictionary with:(Array with:self with:selector with:oldMethod).
+
+    "/
     "/ also notify a change of Smalltalk;
     "/ this allows a dependent of Smalltalk to watch all class
     "/ changes (no need for observing all classes)
--- a/Block.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/Block.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -681,7 +679,6 @@
 ! !
 
 
-
 !Block methodsFor:'accessing'!
 
 home
@@ -1562,11 +1559,10 @@
 
     argArray := argArrayIn.
     (argArray notNil and:[(argArray class ~~ Array) and:[argArray isArray not]]) ifTrue:[
-        argArray isCollection ifTrue:[
-            argArray := argArray asArray
-        ] ifFalse:[
+        argArray isCollection ifFalse:[
             ^ self badArgumentArray:argArray
         ].
+        argArray := argArray asArray.
     ].
     (argArray size ~~ nargs) ifTrue:[
         ^ self wrongNumberOfArguments:argArray size
@@ -1828,11 +1824,10 @@
 
     argArray := argArrayIn.
     (argArray notNil and:[(argArray class ~~ Array) and:[argArray isArray not]]) ifTrue:[
-        argArray isCollection ifTrue:[
-            argArray := argArray asArray
-        ] ifFalse:[
+        argArray isCollection ifFalse:[
             ^ self badArgumentArray:argArray
         ].
+        argArray := argArray asArray.
     ].
 
     (argArray size < nargs) ifTrue:[
@@ -1995,11 +1990,10 @@
 
     argArray := argArrayIn.
     (argArray notNil and:[(argArray class ~~ Array) and:[argArray isArray not]]) ifTrue:[
-        argArray isCollection ifTrue:[
-            argArray := argArray asArray
-        ] ifFalse:[
+        argArray isCollection ifFalse:[
             ^ self badArgumentArray:argArray
         ].
+        argArray := argArray asArray.
     ].
     numArgsProvided := argArray size.
 %{
--- a/ByteArray.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/ByteArray.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1226,6 +1226,7 @@
 beImmutable
     "make myself write-protected"
 
+    super beImmutable.
     self class == ByteArray ifTrue:[
         self changeClassTo:ImmutableByteArray.
     ] ifFalse:[
--- a/Class.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/Class.st	Sun Oct 09 21:28:18 2016 +0100
@@ -967,7 +967,11 @@
         ^ #()
     ].
     classvars isString ifTrue:[
-        classvars := classvars asCollectionOfWords collect:[:varName| varName asSymbol] as:Array.
+        classvars isEmpty ifTrue:[
+            classvars := #().
+        ] ifFalse:[
+            classvars := classvars asCollectionOfWords collect:[:varName| varName asSymbol] as:Array.
+        ].
         ^ classvars
     ].
 
--- a/ClassBuilder.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/ClassBuilder.st	Sun Oct 09 21:28:18 2016 +0100
@@ -355,7 +355,11 @@
             type == #words ifTrue:[
                 wordsBoolean := true
             ] ifFalse:[
+                type == #variable ifTrue:[
+                    pointersBoolean := true
+                ] ifFalse:[
 self halt:'todo'.
+                ]
             ]
         ]
     ].
--- a/ClassDescription.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/ClassDescription.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
@@ -1061,7 +1059,11 @@
         ^ #()
     ].
     instvars isString ifTrue:[
-        instvars := (instvars asCollectionOfWords collect:[:varName| varName asSymbol]) asArray.
+        instvars isEmpty ifTrue:[
+            instvars := #().
+        ] ifFalse:[
+            instvars := instvars asCollectionOfWords collect:[:varName| varName asSymbol] as:Array.
+        ].
     ].
 
     ^ instvars
@@ -1251,7 +1253,10 @@
     (super addSelector:newSelector withMethod:newMethod) ifTrue:[
         "/ only write change records for changes to non-anonymous classes
         self theNonMetaclass containingNameSpace notNil ifTrue:[
-            self addChangeRecordForMethod:newMethod fromOld:oldMethod.
+            "/ just in case addSelector:withMethod: was redefined to ignore this
+            newMethod selector == newSelector ifTrue:[
+                self addChangeRecordForMethod:newMethod fromOld:oldMethod.
+            ]
         ]
     ].
 
@@ -3203,13 +3208,7 @@
      This does NOT include the metaclasses categories or the superclass categories.
      The returned collection is not sorted by any order."
 
-    |newList|
-
-    newList := Set new.
-    self methodDictionary do:[:aMethod |
-	newList add:(aMethod category ? '* no category *')
-    ].
-    ^ newList
+    ^ self methodCategories
 
     "
      Point categories
@@ -3292,6 +3291,29 @@
     "Modified: 1.4.1997 / 15:49:49 / stefan"
 !
 
+methodCategories
+    "Return a collection of the method-categories known in the receiver class.
+     This does NOT include the metaclasses categories or the superclass categories.
+     The returned collection is not sorted by any order."
+
+    |newList|
+
+    newList := Set new.
+    self methodDictionary do:[:aMethod |
+        newList add:(aMethod category ? '* no category *')
+    ].
+    ^ newList
+
+    "
+     Point methodCategories
+     Point class methodCategories
+    "
+
+    "Modified: 16.4.1996 / 18:06:11 / cg"
+    "Modified: 12.6.1996 / 11:25:59 / stefan"
+    "Created: 1.4.1997 / 15:57:18 / stefan"
+!
+
 methodsInCategory:aCategory
     "helper for fileOut: 
      return an unsorted collection of methods from a given category"
--- a/CompiledCode.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/CompiledCode.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1956,10 +1956,10 @@
      refers to aLiteral (i.e. a deep search)"
 
     self literalsDo: [ :el |
-	el == aLiteral ifTrue:[^true].
-	el class == Array ifTrue:[
-	    (el refersToLiteral: aLiteral) ifTrue: [^true]
-	]
+        el == aLiteral ifTrue:[^true].
+        el isArray ifTrue:[
+            (el refersToLiteral: aLiteral) ifTrue: [^true]
+        ]
     ].
     ^ false
 
@@ -1977,10 +1977,10 @@
      is symbolic and matches aMatchPattern (i.e. a deep search)"
 
     self literalsDo: [ :el |
-	(el isSymbol and:[ aMatchPattern match: el]) ifTrue:[^true].
-	el class == Array ifTrue:[
-	    (el refersToLiteralMatching: aMatchPattern) ifTrue: [^true]
-	]
+        (el isSymbol and:[ aMatchPattern match: el]) ifTrue:[^true].
+        el isArray ifTrue:[
+            (el refersToLiteralMatching: aMatchPattern) ifTrue: [^true]
+        ]
     ].
     ^ false
 
--- a/ExecutableFunction.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/ExecutableFunction.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
 	      All Rights Reserved
@@ -88,21 +90,22 @@
 
 code
     "return the code field. This is not an object but the address of the machine instructions. 
-     Therefore an integer representing the code-address is returned"
+     Therefore an externalAddress representing the code-address is returned"
 
 %{  /* NOCONTEXT */
     unsigned INT addr;
 
     if (__INST(code_) != nil) {
         
-        RETURN (__MKEXTERNALADDRESS(__INST(code_)));
 #ifdef OLD
+        // returned an integer in very old versions.
         addr = (unsigned INT)__INST(code_);
         if (addr <= _MAX_INT) {
             RETURN ( __mkSmallInteger(addr) );
         }
         RETURN ( __MKUINT(addr));
 #endif
+        RETURN (__MKEXTERNALADDRESS(__INST(code_)));
     }
 %}.
     ^ nil
--- a/ExternalFunction.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/ExternalFunction.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
 	      All Rights Reserved
@@ -11,6 +13,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 ExecutableFunction subclass:#ExternalFunction
 	instanceVariableNames:'name moduleHandle'
 	classVariableNames:'InvalidCustomFunctionSignal'
@@ -420,13 +424,14 @@
 !ExternalFunction methodsFor:'accessing'!
 
 moduleHandle
-    "return the functions moduleHandle (nil if not loaded dynamically)"
+    "return the function's moduleHandle 
+     (nil if not loaded dynamically)"
 
     ^ moduleHandle
 !
 
 name
-    "return the functions name"
+    "return the function's name"
 
     ^ name
 ! !
@@ -994,4 +999,5 @@
     ^ '$Header$'
 ! !
 
+
 ExternalFunction initialize!
--- a/ExternalLibraryFunction.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/ExternalLibraryFunction.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2004 by eXept Software AG
 	      All Rights Reserved
@@ -229,7 +227,7 @@
   Synchronous vs. Asynchronous calls:
 
     by default, foreign function calls are synchronous, effectively blocking the whole ST/X system
-    (that is by purpose,´because most C-code is not prepared for being interrupted, and also, normal
+    (that is by purpose,because most C-code is not prepared for being interrupted, and also, normal
      code is not prepared for a garbage collector to move objects around, while another C thread might
      access the data...).
     Therefore, the following will block all ST/X activity for 10 seconds
@@ -450,9 +448,10 @@
 
 ffiTypeSymbolForType:aType
     "map type to one of the ffi-supported ones:
-	sint8, sint16, sint32, sint64
-	uint8, uint16, uint32, uint64
-	bool void pointer handle
+        sint8, sint16, sint32, sint64
+        uint8, uint16, uint32, uint64
+        long ulong int uint
+        bool float double void pointer handle
     "
 
     aType == #sint8           ifTrue:[^ aType ].
@@ -523,22 +522,23 @@
     aType == #HANDLE          ifTrue:[^ #pointer ].
     aType == #HRESULT         ifTrue:[^ #hresult ].
 
+    aType == #BSTR            ifTrue:[^ #wcharPointer].
+
     "/ care for 64bit machines
     aType == #SIZE_T          ifTrue:[^ ExternalAddress pointerSize == 8 ifTrue:[#uint64] ifFalse:[#uint32]].
-    aType == #BSTR            ifTrue:[^ #wcharPointer].
 
     (aType isString or:[aType isSymbol]) ifFalse:[
-	CType isNil ifTrue:[
-	    self error:'unknown type'.
-	].
-	^ aType typeSymbol.
+        CType isNil ifTrue:[
+            self error:'unknown type'.
+        ].
+        ^ aType typeSymbol.
     ].
 
     (aType endsWith:'*') ifTrue:[
-	^ #pointer.
+        ^ #pointer.
     ].
     (aType endsWith:'Pointer') ifTrue:[
-	^ #pointer.
+        ^ #pointer.
     ].
     ^ aType
 
@@ -921,9 +921,6 @@
         or:[ LastModuleHandleName ~= moduleNameUsed ]]) ifTrue:[
 
             handle := self loadLibrary:moduleNameUsed.
-            (handle isNil or:[handle = -1]) ifTrue:[
-                self error:('Cannot find or load dll/module: "%1"' bindWith: moduleNameUsed).
-            ].
             LastModuleHandleHolder := WeakArray with:handle.
             LastModuleHandleName := moduleNameUsed.
         ].
@@ -951,6 +948,10 @@
 
     |handle nameString filename dllPathes|
 
+    (ObjectFileLoader isNil or:[ObjectFileLoader canLoadObjectFiles not]) ifTrue:[
+        self error:('ObjectFileLoader class missing: cannot load dll/module: "%1"' bindWith:nameString).
+    ].
+
     filename := dllName.
     DllMapping notNil ifTrue:[
         filename := DllMapping at:filename ifAbsent:[ filename ]
@@ -985,6 +986,9 @@
         ^ self loadLibrary:(filename withSuffix:ObjectFileLoader sharedLibrarySuffix)
     ].
 
+    self 
+        error:('Cannot find or load dll/module: "%1"' bindWith:nameString)
+        mayProceed:true.
     ^ nil
 
     "Modified: / 10-04-2012 / 12:21:06 / cg"
--- a/Filename.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/Filename.st	Sun Oct 09 21:28:18 2016 +0100
@@ -2264,23 +2264,44 @@
      Notice: this enumerates strings; see also
      #directoryContentsAsFilenamesDo:, which enumerates fileName objects."
 
-    |s|
+    |s files|
 
     s := DirectoryStream directoryNamed:self osNameForDirectoryContents.
     "check for nil, in order to allow to proceed from an OpenError"
     s notNil ifTrue:[
+        "/ the old code did a recursive call with the stream open.
+        "/ for very very deep hierarchies, this lead to having too many file streams open for
+        "/ some operating systems.
+        "/ (and therefore to a blocked system, sooner or later, when running out of open files)
+        "/ new code reads the directory first, then does the recursion.
+
+"/        [
+"/            [s atEnd] whileFalse:[
+"/                |fn|
+"/
+"/                fn := s nextLine.
+"/                (fn notNil and:[fn ~= '.' and:[fn ~= '..']]) ifTrue:[
+"/                    aBlock value:fn
+"/                ].
+"/            ].
+"/        ] ensure:[
+"/            s close.
+"/        ].
+        files := OrderedCollection new.
+        
         [
             [s atEnd] whileFalse:[
                 |fn|
 
                 fn := s nextLine.
                 (fn notNil and:[fn ~= '.' and:[fn ~= '..']]) ifTrue:[
-                    aBlock value:fn
+                    files add:fn
                 ].
             ].
         ] ensure:[
             s close.
-        ].
+        ]. 
+        files do:aBlock
     ].
 
     "
--- a/ImmutableArray.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/ImmutableArray.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1995 by Claus Gittinger
 	      All Rights Reserved
@@ -119,6 +117,13 @@
 
 !ImmutableArray methodsFor:'converting'!
 
+asArray
+    "return the receiver as an array. I am already.
+     Use asNewArray, or asMutableCollection if you need a copy for modification"
+
+    ^ self 
+!
+
 asImmutableArray
     ^ self
 !
@@ -127,6 +132,24 @@
     "return a writable copy of myself"
 
     ^ self copy changeClassTo:Array
+!
+
+asNewArray
+    "return the receiver as an unique new array."
+
+    ^ self copy
+!
+
+beImmutable
+    "that's what I am"
+
+    ^ self
+!
+
+beMutable
+    "you never go back"
+
+    ^ self shouldNotImplement
 ! !
 
 !ImmutableArray methodsFor:'copying'!
--- a/ImmutableByteArray.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/ImmutableByteArray.st	Sun Oct 09 21:28:18 2016 +0100
@@ -206,6 +206,12 @@
     ^ self
 !
 
+beMutable
+    "you never go back"
+
+    ^ self shouldNotImplement
+!
+
 beUnsigned
     "that's what I am-"
 
--- a/ImmutableString.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/ImmutableString.st	Sun Oct 09 21:28:18 2016 +0100
@@ -125,6 +125,18 @@
     "return a writable copy of myself"
 
     ^ self copy changeClassTo:String
+!
+
+beImmutable
+    "that's what I am"
+
+    ^ self
+!
+
+beMutable
+    "you never go back"
+
+    ^ self shouldNotImplement
 ! !
 
 !ImmutableString methodsFor:'copying'!
--- a/Method.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/Method.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1059,7 +1059,6 @@
     "Modified (format): / 18-11-2011 / 14:47:06 / cg"
 ! !
 
-
 !Method methodsFor:'accessing-visibility'!
 
 isIgnored
@@ -1981,7 +1980,7 @@
     classAndSelector notNil ifTrue:[
         (classAndSelector methodClass) name printOn:aStream.
         "/ print out in a form that can directly be evaluated (>> is a selector in Behavior)
-        "/ aStream nextPutAll:' » '.
+        "/ aStream nextPutAll:'  '.
         aStream nextPutAll:' >> '.
         (classAndSelector methodSelector) printOn:aStream.
     ] ifFalse:[
@@ -2017,7 +2016,7 @@
     who := self who.
     who notNil ifTrue:[
         "/ in order to not break existing code which parses those strings,
-        "/ do not replace '>>' by ' » '
+        "/ do not replace '>>' by '  '
         ^ who methodClass name , ' >> ' , (who methodSelector storeString)
     ].
     ^ 'unboundMethod'
@@ -2044,21 +2043,21 @@
 
     annotationOrArray := annotation := annotations at: index.
     annotationOrArray isArray ifTrue:[
-	args := annotationOrArray size == 2
-		    ifTrue:[annotationOrArray second]
-		    ifFalse:[#()].
-	args isArray ifFalse:[args := Array with: args].
-	annotation := Annotation
-			method:self
-			key: annotationOrArray first
-			arguments: args.
-	annotation isUnknown ifFalse:[
-	    annotations isImmutable ifTrue:[
-		annotations := annotations asArray
-	    ].
-	    annotations at: index put: annotation.
+        args := annotationOrArray size == 2
+                    ifTrue:[annotationOrArray second]
+                    ifFalse:[#()].
+        args isArray ifFalse:[args := Array with: args].
+        annotation := Annotation
+                        method:self
+                        key: annotationOrArray first
+                        arguments: args.
+        annotation isUnknown ifFalse:[
+            annotations isImmutable ifTrue:[
+                annotations := annotations asMutableCollection
+            ].
+            annotations at: index put: annotation.
 "/            annotation annotatesMethod: self
-	].
+        ].
     ].
     ^annotation
 
@@ -3761,7 +3760,6 @@
     "Created: / 23-07-2012 / 11:16:36 / cg"
 ! !
 
-
 !Method methodsFor:'source management'!
 
 revisionInfo
--- a/MethodWithBreakpoints.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/MethodWithBreakpoints.st	Sun Oct 09 21:28:18 2016 +0100
@@ -174,7 +174,22 @@
     "true if any of my breakpoints is actually enabled"
 
     self breakpointsDo:[:any | 
-        any isEnabled ifTrue:[^ true].
+        any isEnabled ifTrue:[
+            any isTracepoint ifFalse:[ ^ true].
+        ].    
+    ].
+    ^ false.
+!
+
+hasEnabledTracepoints
+    "true if any of my tracepoints is actually enabled"
+
+    self breakpointsDo:[:any | 
+        any isEnabled ifTrue:[
+            any isTracepoint ifTrue:[
+                ^ true
+            ].
+        ].
     ].
     ^ false.
 !
--- a/MiniLogger.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/MiniLogger.st	Sun Oct 09 21:28:18 2016 +0100
@@ -16,7 +16,8 @@
 Object subclass:#MiniLogger
 	instanceVariableNames:''
 	classVariableNames:'ALL DEBUG ENTER ERROR FATAL INFO Instance LEAVE NONE Severities
-		TRACE TRACE0 TRACE1 TRACE2 TRACE3 Threshold WARN WARNING'
+		TRACE TRACE0 TRACE1 TRACE2 TRACE3 Threshold WARN WARNING
+		LogOnTranscript LogOnStderr LogFormat TimestampFormat'
 	poolDictionaries:''
 	category:'System-Debugging-Support'
 !
@@ -47,13 +48,27 @@
 documentation
 "   
     A very simple logger for Smalltalk/X. This one is always present.
-    All `Transcript show: 'Processor [info]: xxx' should be rewritten
-    using Logger.
+    It mimics the protocol of the loggers found in stx:goodies/loggia,
+    which can be activated by setting the global 'Logger' to an instance of
+    on of them.
+    
+    All 
+        `Transcript show: 'Processor [info]: xxx' 
+    should be rewritten over time to use the Logger.
 
+    'Object infoPrint' and 'Object debugPrint' have been changed to
+    forward their message to the global 'Logger' unless nil.
+    
     Usage:
+        Logger info: 'Hello world'.
+        Logger debug: 'Hello world'.
+        Logger warning: 'Hello world'.
+        Logger error: 'Hello world'.
 
-        Logger info: 'Hello worlds'.
-
+    to disable logging:
+        MiniLogger logOnTranscript:false.
+        MiniLogger logOnStderr:false.
+        
     For more examples, see #examples.
 
     [author:]
@@ -143,6 +158,100 @@
     "Modified: / 13-08-2014 / 14:36:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!MiniLogger class methodsFor:'accessing-log format'!
+
+logFormat
+    "will be used for the log message as:
+        %1 [%2] (%3): %4
+    with %1: facility (area)
+    with %2: secerity (area)
+    with %3: timestamp 
+    with %4: caller/originator 
+    with %5: message"
+    
+    ^ LogFormat ? '%1 [%2] (%3): %5'
+
+    "
+     MiniLogger logFormat:'%1 [%2]: %5'.
+     'hello' errorPrintCR.
+     MiniLogger logFormat:'%3 %1 [%2]: %5'.
+     'hello' errorPrintCR.
+     MiniLogger logFormat:nil.
+     'hello' errorPrintCR.
+    "
+!
+
+logFormat:aFormatString
+    "will be used for the log message as:
+        %1 [%2] (%3): %4
+            with %1: facility (area)
+            with %2: secerity (area)
+            with %3: timestamp 
+            with %4: caller/originator 
+            with %5: message.
+     Pass anil argument to return to the default format.        
+    "
+    
+    LogFormat := aFormatString
+
+    "
+     MiniLogger logFormat:'%1 [%2]: %5'.
+     'hello' errorPrintCR.
+     MiniLogger logFormat:'%3 %1 [%2]: %5'.
+     'hello' errorPrintCR.
+     MiniLogger logFormat:nil.
+     'hello' errorPrintCR.
+    "
+!
+
+logOnStderr 
+    ^ LogOnStderr ? true
+!
+
+logOnStderr:aBoolean
+    "enable/disable loggin on stderr"
+    
+    LogOnStderr := aBoolean
+
+    "
+     MiniLogger logOnStderr:false
+     MiniLogger logOnTranscript:false
+
+     MiniLogger logOnStderr:true
+     MiniLogger logOnTranscript:true
+    "
+!
+
+logOnTranscript
+    ^ LogOnTranscript ? true
+!
+
+logOnTranscript:aBoolean
+    "enable/disable loggin on the Transcript"
+
+    LogOnTranscript := aBoolean
+
+    "
+     MiniLogger logOnStderr:false
+     MiniLogger logOnTranscript:false
+
+     MiniLogger logOnStderr:true
+     MiniLogger logOnTranscript:true
+    "
+!
+
+timestampFormat
+    "will be used for the log message"
+    
+    ^ TimestampFormat ? '%(year)-%(mon)-%(day) %h:%m:%s.%i'.
+!
+
+timestampFormat:aTimestampFormatString
+    "will be used for the log message"
+    
+    TimestampFormat := aTimestampFormatString
+! !
+
 !MiniLogger class methodsFor:'accessing-severities'!
 
 severityDEBUG
@@ -317,6 +426,8 @@
 
     | severityXlated messageXlated |
 
+    (self logOnStderr or:[self logOnTranscript]) ifFalse:[^ self].
+
     severityXlated := severity.
 
     "/ Be backward compatible, allow for symbolic severities
@@ -362,9 +473,13 @@
     severityXlated value < Threshold value ifTrue:[ ^ self ].
     messageXlated := message value asString.
 
-    self log: messageXlated severity: severityXlated facility: facility originator: originator attachment: attachment on:Stderr.
-    (Transcript isView) ifTrue:[ 
-        self log: messageXlated severity: severityXlated facility: facility originator: originator attachment: attachment on:Transcript
+    self logOnStderr ifTrue:[
+        self log: messageXlated severity: severityXlated facility: facility originator: originator attachment: attachment on:Stderr.
+    ].
+    self logOnTranscript ifTrue:[
+        (Transcript isView) ifTrue:[ 
+            self log: messageXlated severity: severityXlated facility: facility originator: originator attachment: attachment on:Transcript
+        ].
     ].
 
     "
@@ -747,15 +862,15 @@
 log: message severity: severity facility: facilityArg originator: originator attachment: attachment on:aStream
     "Pricipal logging method. This mimics VM __stxLog__()"
 
-    | facility severityName messageProperlyEncoded words|
+    |facility severityName messageProperlyEncoded words messageAsSent|
 
     facility := facilityArg.
     messageProperlyEncoded := message.
     severityName := severity name.
-    
+
     "/ If the message is Unicode 16/32 string and stream is external,
-    "/ we have to recode the message using locale-specific encoding 
-    (message isWideString and:[ aStream isExternalStream ]) ifTrue:[ 
+    "/ we have to recode the message using locale-specific encoding
+    (message isWideString and:[ aStream isExternalStream ]) ifTrue:[
         OperatingSystem isMSWINDOWSlike ifTrue:[
             messageProperlyEncoded := message utf8Encoded.
         ] ifFalse:[
@@ -763,7 +878,7 @@
         ]
     ].
     messageProperlyEncoded := messageProperlyEncoded withoutSeparators.
-    
+
     "/ hack to allow calls from infPrint/errorPrint.
     "/ if this is an oldStyle infoPrint or errorPrint, do not append another facility and severity
     words := message asCollectionOfWords.
@@ -780,23 +895,23 @@
             messageProperlyEncoded := (messageProperlyEncoded copyFrom:2) withoutSeparators.
         ].
     ].
-    
+    messageAsSent := (self logFormat
+                bindWith:(facility ? 'STX')
+                with:severityName
+                with:(Timestamp now printStringFormat:(self timestampFormat))
+                with:originator printString
+                with:messageProperlyEncoded).
+    aStream isView ifFalse:[
+        messageAsSent := messageAsSent string utf8Encoded
+    ].
+
     "/ Timestamp now printOn:aStream format:'%(year)-%(mon)-%(day) %h:%m:%s.%i'.
     "/ aStream space.
-    aStream
-        nextPutAll: facility ? 'STX';
-        nextPutAll:' [';
-        nextPutAll: severityName;
-        nextPutAll:']'.
-
-    aStream nextPutAll:' ('.
-    Timestamp now printOn:aStream format:'%(year)-%(mon)-%(day) %h:%m:%s.%i'.
-    aStream nextPutAll:'): '.
-
-    aStream nextPutAll: messageProperlyEncoded.
-    aStream cr.
+    aStream nextPutLine: messageAsSent
 
     "
+     'hello' infoPrintCR.
+
      Logger log:'test message' severity: #debug facility: 'TEST'
      Logger log:'test message' severity: #info facility: 'TEST'
      Logger log:'test message' severity: #warning facility: 'TEST'
--- a/Object.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/Object.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
-	      All Rights Reserved
+              All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -14,22 +14,22 @@
 "{ NameSpace: Smalltalk }"
 
 nil subclass:#Object
-	instanceVariableNames:''
-	classVariableNames:'AbortAllSignal AbortSignal ActivityNotificationSignal
-		DebuggerHooks DeepCopyErrorSignal Dependencies
-		ElementOutOfBoundsSignal EnabledBreakPoints ErrorRecursion
-		ErrorSignal FinalizationLobby HaltSignal IndexNotFoundSignal
-		InfoPrinting InformationSignal InternalErrorSignal
-		KeyNotFoundSignal MessageNotUnderstoodSignal
-		NonIntegerIndexSignal NonWeakDependencies NotFoundSignal
-		OSSignalInterruptSignal ObjectAttributes
-		ObjectAttributesAccessLock PartialErrorPrintLine
-		PartialInfoPrintLine PrimitiveFailureSignal
-		RecursionInterruptSignal RecursiveStoreStringSignal
-		SubscriptOutOfBoundsSignal SynchronizationSemaphores
-		UserInterruptSignal UserNotificationSignal WarningSignal'
-	poolDictionaries:''
-	category:'Kernel-Objects'
+        instanceVariableNames:''
+        classVariableNames:'AbortAllSignal AbortSignal ActivityNotificationSignal
+                DebuggerHooks DeepCopyErrorSignal Dependencies
+                ElementOutOfBoundsSignal EnabledBreakPoints ErrorRecursion
+                ErrorSignal FinalizationLobby HaltSignal IndexNotFoundSignal
+                InfoPrinting InformationSignal InternalErrorSignal
+                KeyNotFoundSignal MessageNotUnderstoodSignal
+                NonIntegerIndexSignal NonWeakDependencies NotFoundSignal
+                OSSignalInterruptSignal ObjectAttributes
+                ObjectAttributesAccessLock PartialErrorPrintLine
+                PartialInfoPrintLine PrimitiveFailureSignal
+                RecursionInterruptSignal RecursiveStoreStringSignal
+                SubscriptOutOfBoundsSignal SynchronizationSemaphores
+                UserInterruptSignal UserNotificationSignal WarningSignal'
+        poolDictionaries:''
+        category:'Kernel-Objects'
 !
 
 !Object class methodsFor:'documentation'!
@@ -37,7 +37,7 @@
 copyright
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
-	      All Rights Reserved
+              All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -121,52 +121,52 @@
 
    [Class variables:]
 
-	ErrorSignal     <Signal>        Signal raised for error/error: messages
-					also, parent of all other signals.
-
-	HaltSignal      <Signal>        Signal raised for halt/halt: messages
-
-	MessageNotUnderstoodSignal      Signals raised for various error conditions
-	UserInterruptSignal
-	RecursionInterruptSignal
-	ExceptionInterruptSignal
-	SubscriptOutOfBoundsSignal
-	NonIntegerIndexSignal
-	NotFoundSignal
-	KeyNotFoundSignal
-	ElementOutOfBoundsSignal
-	InformationSignal
-	WarningSignal
-	DeepCopyErrorSignal
-	InternalErrorSignal
-
-	AbortSignal      <Signal>       Signal raised by debugger, to abort a computation
-					BUT, the debugger will only raise it if it is handled.
-					By handling the abortSignal, you can control where the
-					debuggers abort-function resumes execution in case of
-					an error.
-
-	ErrorRecursion   <Boolean>      controls behavior when recursive errors occur (i.e.
-					an error while handling an error).
-
-	Dependencies     <WeakDependencyDictionary>
-					keeps track of object dependencies.
-
-	InfoPrinting     <Boolean>      controls weather informational messages
-					are printed.
-
-	ActivityNotificationSignal <QuerySignal>
-					 raised on #activityNotification:
-
-	NonWeakDependencies <Dictionary> keeps track of object dependencies.
-					 Dependents stay alive.
-
-	SynchronizationSemaphores <WeakIdentityDictionary>
-					 Semaphores for per-object-monitor.
+        ErrorSignal     <Signal>        Signal raised for error/error: messages
+                                        also, parent of all other signals.
+
+        HaltSignal      <Signal>        Signal raised for halt/halt: messages
+
+        MessageNotUnderstoodSignal      Signals raised for various error conditions
+        UserInterruptSignal
+        RecursionInterruptSignal
+        ExceptionInterruptSignal
+        SubscriptOutOfBoundsSignal
+        NonIntegerIndexSignal
+        NotFoundSignal
+        KeyNotFoundSignal
+        ElementOutOfBoundsSignal
+        InformationSignal
+        WarningSignal
+        DeepCopyErrorSignal
+        InternalErrorSignal
+
+        AbortSignal      <Signal>       Signal raised by debugger, to abort a computation
+                                        BUT, the debugger will only raise it if it is handled.
+                                        By handling the abortSignal, you can control where the
+                                        debuggers abort-function resumes execution in case of
+                                        an error.
+
+        ErrorRecursion   <Boolean>      controls behavior when recursive errors occur (i.e.
+                                        an error while handling an error).
+
+        Dependencies     <WeakDependencyDictionary>
+                                        keeps track of object dependencies.
+
+        InfoPrinting     <Boolean>      controls weather informational messages
+                                        are printed.
+
+        ActivityNotificationSignal <QuerySignal>
+                                         raised on #activityNotification:
+
+        NonWeakDependencies <Dictionary> keeps track of object dependencies.
+                                         Dependents stay alive.
+
+        SynchronizationSemaphores <WeakIdentityDictionary>
+                                         Semaphores for per-object-monitor.
 
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 
 "
 ! !
@@ -225,25 +225,25 @@
     "called only once - initialize signals"
 
     ErrorSignal isNil ifTrue:[
-	self initSignals.
-	ErrorRecursion := true.
+        self initSignals.
+        ErrorRecursion := true.
     ].
 
     ObjectAttributes isNil ifTrue:[
-	ObjectAttributes := WeakIdentityDictionary new.
-	ObjectAttributesAccessLock := RecursionLock new.
+        ObjectAttributes := WeakIdentityDictionary new.
+        ObjectAttributesAccessLock := RecursionLock new.
     ].
     Dependencies isNil ifTrue:[
-	Dependencies := WeakDependencyDictionary new.
+        Dependencies := WeakDependencyDictionary new.
     ].
     NonWeakDependencies isNil ifTrue:[
-	NonWeakDependencies := IdentityDictionary new.
+        NonWeakDependencies := IdentityDictionary new.
     ].
     SynchronizationSemaphores isNil ifTrue:[
-	SynchronizationSemaphores := WeakIdentityDictionary new.
+        SynchronizationSemaphores := WeakIdentityDictionary new.
     ].
     FinalizationLobby isNil ifTrue:[
-	FinalizationLobby := Registry new.
+        FinalizationLobby := Registry new.
     ].
 
     "/ initialize InfoPrinting to the VM's infoPrint setting
@@ -424,13 +424,13 @@
 
     "
      RecursiveStoreError handle:[:ex |
-	self halt
+        self halt
      ] do:[
-	|a|
-
-	a := Array new:1.
-	a at:1 put:a.
-	a storeOn:Transcript
+        |a|
+
+        a := Array new:1.
+        a at:1 put:a.
+        a storeOn:Transcript
      ]
     "
 
@@ -606,7 +606,7 @@
 explore
     (self confirm:'The Squeak explorer has not yet been ported to ST/X\\Inspect instead ?' withCRs)
     ifTrue:[
-	self inspect
+        self inspect
     ]
 !
 
@@ -637,13 +637,13 @@
 !
 
 stringForReadout
-	^ self stringRepresentation
+        ^ self stringRepresentation
 !
 
 stringRepresentation
-	"Answer a string that represents the receiver.  For most objects this is simply its printString, but for strings themselves, it's themselves.  6/12/96 sw"
-
-	^ self printString
+        "Answer a string that represents the receiver.  For most objects this is simply its printString, but for strings themselves, it's themselves.  6/12/96 sw"
+
+        ^ self printString
 !
 
 veryDeepCopy
@@ -700,9 +700,9 @@
      this is a synthetic selector, generated by the compiler,
      if a construct of the form expr[idx...] is parsed.
      I.e.
-	v[n]
+        v[n]
      generates
-	v _at: n
+        v _at: n
     "
 
     ^ self at:index
@@ -715,9 +715,9 @@
      this is a synthetic selector, generated by the compiler,
      if a construct of the form expr[idx...] is parsed.
      I.e.
-	v[n]
+        v[n]
      generates
-	v _at: n
+        v _at: n
     "
 
     ^ self at:index put:value
@@ -736,20 +736,20 @@
 
     anonCls := self perform:classGetter ifNotUnderstood:nil.
     anonCls isNil ifTrue:[
-	anonCls := myClass
-		subclass:(myClass name,'+',slotName) asSymbol
-		instanceVariableNames:slotName
-		classVariableNames:''
-		poolDictionaries:'' category:nil
-		inEnvironment:nil.
-	anonCls compile:('%1 ^  %1' bindWith:slotName).
-	anonCls compile:('%1:v %1 := v' bindWith:slotName).
-	Class withoutUpdatingChangesDo:[
-	    |m|
-	    m := Compiler compile:('__get_',slotName,' ^ #fooBar' bindWith:slotName) forClass:myClass install:false.
-	    m literalAt:(m literals indexOf:#fooBar) put:anonCls.
-	    myClass addSelector:classGetter withMethod:m.
-	].
+        anonCls := myClass
+                subclass:(myClass name,'+',slotName) asSymbol
+                instanceVariableNames:slotName
+                classVariableNames:''
+                poolDictionaries:'' category:nil
+                inEnvironment:nil.
+        anonCls compile:('%1 ^  %1' bindWith:slotName).
+        anonCls compile:('%1:v %1 := v' bindWith:slotName).
+        Class withoutUpdatingChangesDo:[
+            |m|
+            m := Compiler compile:('__get_',slotName,' ^ #fooBar' bindWith:slotName) forClass:myClass install:false.
+            m literalAt:(m literals indexOf:#fooBar) put:anonCls.
+            myClass addSelector:classGetter withMethod:m.
+        ].
     ].
     newObj := anonCls cloneFrom:self.
     self become:newObj.
@@ -806,8 +806,8 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     {
-	int idx1Based = index.intValue();   // st index is 1 based
-	return context._RETURN( self.basicAt( idx1Based ));
+        int idx1Based = index.intValue();   // st index is 1 based
+        return context._RETURN( self.basicAt( idx1Based ));
     }
     /* NOTREACHED */
 #else
@@ -822,258 +822,258 @@
      * and SmallInteger
      */
     if (__isSmallInteger(index)) {
-	myClass = __qClass(self);
-	indx = __intVal(index) - 1;
-	n /* nInstVars */ = __intVal(__ClassInstPtr(myClass)->c_ninstvars);
-	n /* nInstBytes */ = OHDR_SIZE + __OBJS2BYTES__(n /* nInstVars */);
-	nbytes = __qSize(self) - n /* nInstBytes */;
-	pFirst = (char *)(__InstPtr(self)) + n /* nInstBytes */;
-
-	switch ((INT)(__ClassInstPtr(myClass)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
-	    case __MASKSMALLINT(POINTERARRAY):
-		/*
-		 * pointers
-		 */
-		if ((unsigned)indx < (__BYTES2OBJS__(nbytes))) {
-		    OBJ *op;
-
-		    op = (OBJ *)pFirst + indx;
-		    RETURN ( *op );
-		}
-		break;
-
-	    case __MASKSMALLINT(WKPOINTERARRAY):
-		if ((unsigned)indx < (__BYTES2OBJS__(nbytes))) {
-		    OBJ *op;
-		    OBJ el;
-
-		    op = (OBJ *)pFirst + indx;
-		    el = *op;
-		    el = __WEAK_READ__(self, el);
-		    RETURN ( el );
-		}
-		break;
-
-	    case __MASKSMALLINT(BYTEARRAY):
-		/*
-		 * (unsigned) bytes
-		 */
-		if ((unsigned)indx < nbytes) {
-		    unsigned char *cp;
-
-		    cp = (unsigned char *)pFirst + indx;
-		    RETURN ( __mkSmallInteger( (*cp & 0xFF)) );
-		}
-		break;
-
-	    case __MASKSMALLINT(FLOATARRAY):
-		/*
-		 * native floats
-		 */
+        myClass = __qClass(self);
+        indx = __intVal(index) - 1;
+        n /* nInstVars */ = __intVal(__ClassInstPtr(myClass)->c_ninstvars);
+        n /* nInstBytes */ = OHDR_SIZE + __OBJS2BYTES__(n /* nInstVars */);
+        nbytes = __qSize(self) - n /* nInstBytes */;
+        pFirst = (char *)(__InstPtr(self)) + n /* nInstBytes */;
+
+        switch ((INT)(__ClassInstPtr(myClass)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
+            case __MASKSMALLINT(POINTERARRAY):
+                /*
+                 * pointers
+                 */
+                if ((unsigned)indx < (__BYTES2OBJS__(nbytes))) {
+                    OBJ *op;
+
+                    op = (OBJ *)pFirst + indx;
+                    RETURN ( *op );
+                }
+                break;
+
+            case __MASKSMALLINT(WKPOINTERARRAY):
+                if ((unsigned)indx < (__BYTES2OBJS__(nbytes))) {
+                    OBJ *op;
+                    OBJ el;
+
+                    op = (OBJ *)pFirst + indx;
+                    el = *op;
+                    el = __WEAK_READ__(self, el);
+                    RETURN ( el );
+                }
+                break;
+
+            case __MASKSMALLINT(BYTEARRAY):
+                /*
+                 * (unsigned) bytes
+                 */
+                if ((unsigned)indx < nbytes) {
+                    unsigned char *cp;
+
+                    cp = (unsigned char *)pFirst + indx;
+                    RETURN ( __mkSmallInteger( (*cp & 0xFF)) );
+                }
+                break;
+
+            case __MASKSMALLINT(FLOATARRAY):
+                /*
+                 * native floats
+                 */
 # ifdef __NEED_FLOATARRAY_ALIGN
-		if ((INT)pFirst & (__FLOATARRAY_ALIGN-1)) {
-		    int delta = __FLOATARRAY_ALIGN - ((INT)pFirst & (__FLOATARRAY_ALIGN-1));
-
-		    pFirst += delta;
-		    nbytes -= delta;
-		}
+                if ((INT)pFirst & (__FLOATARRAY_ALIGN-1)) {
+                    int delta = __FLOATARRAY_ALIGN - ((INT)pFirst & (__FLOATARRAY_ALIGN-1));
+
+                    pFirst += delta;
+                    nbytes -= delta;
+                }
 # endif
-		if ((unsigned)indx < (nbytes / sizeof(float))) {
-		    float *fp;
-		    float f;
-		    OBJ v;
-
-		    fp = (float *)pFirst + indx;
-		    f = *fp;
-		    if (f == 0.0) {
-			v = STX__float0;
-		    } else {
-			__qMKSFLOAT(v, f);
-		    }
-		    RETURN (v);
-		}
-		break;
-
-	    case __MASKSMALLINT(DOUBLEARRAY):
-		/*
-		 * native doubles
-		 */
+                if ((unsigned)indx < (nbytes / sizeof(float))) {
+                    float *fp;
+                    float f;
+                    OBJ v;
+
+                    fp = (float *)pFirst + indx;
+                    f = *fp;
+                    if (f == 0.0) {
+                        v = STX__float0;
+                    } else {
+                        __qMKSFLOAT(v, f);
+                    }
+                    RETURN (v);
+                }
+                break;
+
+            case __MASKSMALLINT(DOUBLEARRAY):
+                /*
+                 * native doubles
+                 */
 # ifdef __NEED_DOUBLE_ALIGN
-		if ((INT)pFirst & (__DOUBLE_ALIGN-1)) {
-		    int delta = __DOUBLE_ALIGN - ((INT)pFirst & (__DOUBLE_ALIGN-1));
-
-		    pFirst += delta;
-		    nbytes -= delta;
-		}
+                if ((INT)pFirst & (__DOUBLE_ALIGN-1)) {
+                    int delta = __DOUBLE_ALIGN - ((INT)pFirst & (__DOUBLE_ALIGN-1));
+
+                    pFirst += delta;
+                    nbytes -= delta;
+                }
 # endif
-		if ((unsigned)indx < (nbytes / sizeof(double))) {
-		    double *dp;
-		    double d;
-		    OBJ v;
-
-		    dp = (double *)pFirst + indx;
-		    d = *dp;
-		    if (d == 0.0) {
-			v = STX__float0;
-		    } else {
-			__qMKFLOAT(v, d);
-		    }
-		    RETURN (v);
-		}
-		break;
-
-	    case __MASKSMALLINT(WORDARRAY):
-		/*
-		 * unsigned 16bit ints
-		 */
-		/* Notice: the hard coded shifts are by purpose;
-		 * it makes us independent of the short-size of the machine
-		 */
-		if ((unsigned)indx < (nbytes>>1)) {
-		    unsigned short *sp;
-
-		    sp = (unsigned short *)(pFirst + (indx<<1));
-		    RETURN ( __mkSmallInteger( (*sp & 0xFFFF)) );
-		}
-		break;
-
-	    case __MASKSMALLINT(SWORDARRAY):
-		/*
-		 * signed 16bit ints
-		 */
-		/* Notice: the hard coded shifts are by purpose;
-		 * it makes us independent of the short-size of the machine
-		 */
-		if ((unsigned)indx < (nbytes>>1)) {
-		    short *ssp;
-
-		    ssp = (short *)(pFirst + (indx<<1));
-		    RETURN ( __mkSmallInteger( (*ssp) ));
-		}
-		break;
-
-	    case __MASKSMALLINT(LONGARRAY):
-		/*
-		 * unsigned 32bit ints
-		 */
-		/* Notice: the hard coded shifts are by purpose;
-		 * it makes us independent of the int-size of the machine
-		 */
-		if ((unsigned)indx < (nbytes>>2)) {
-		    unsigned int32 ul;
-		    unsigned int32 *lp;
-
-		    lp = (unsigned int32 *)(pFirst + (indx<<2));
-		    ul = *lp;
+                if ((unsigned)indx < (nbytes / sizeof(double))) {
+                    double *dp;
+                    double d;
+                    OBJ v;
+
+                    dp = (double *)pFirst + indx;
+                    d = *dp;
+                    if (d == 0.0) {
+                        v = STX__float0;
+                    } else {
+                        __qMKFLOAT(v, d);
+                    }
+                    RETURN (v);
+                }
+                break;
+
+            case __MASKSMALLINT(WORDARRAY):
+                /*
+                 * unsigned 16bit ints
+                 */
+                /* Notice: the hard coded shifts are by purpose;
+                 * it makes us independent of the short-size of the machine
+                 */
+                if ((unsigned)indx < (nbytes>>1)) {
+                    unsigned short *sp;
+
+                    sp = (unsigned short *)(pFirst + (indx<<1));
+                    RETURN ( __mkSmallInteger( (*sp & 0xFFFF)) );
+                }
+                break;
+
+            case __MASKSMALLINT(SWORDARRAY):
+                /*
+                 * signed 16bit ints
+                 */
+                /* Notice: the hard coded shifts are by purpose;
+                 * it makes us independent of the short-size of the machine
+                 */
+                if ((unsigned)indx < (nbytes>>1)) {
+                    short *ssp;
+
+                    ssp = (short *)(pFirst + (indx<<1));
+                    RETURN ( __mkSmallInteger( (*ssp) ));
+                }
+                break;
+
+            case __MASKSMALLINT(LONGARRAY):
+                /*
+                 * unsigned 32bit ints
+                 */
+                /* Notice: the hard coded shifts are by purpose;
+                 * it makes us independent of the int-size of the machine
+                 */
+                if ((unsigned)indx < (nbytes>>2)) {
+                    unsigned int32 ul;
+                    unsigned int32 *lp;
+
+                    lp = (unsigned int32 *)(pFirst + (indx<<2));
+                    ul = *lp;
 # if __POINTER_SIZE__ == 8
-		    {
-			unsigned INT ull = (unsigned INT)ul;
-			RETURN ( __mkSmallInteger(ull) );
-		    }
+                    {
+                        unsigned INT ull = (unsigned INT)ul;
+                        RETURN ( __mkSmallInteger(ull) );
+                    }
 # else
-		    if (ul <= _MAX_INT) {
-			RETURN ( __mkSmallInteger(ul) );
-		    }
-		    RETURN ( __MKULARGEINT(ul) );
+                    if (ul <= _MAX_INT) {
+                        RETURN ( __mkSmallInteger(ul) );
+                    }
+                    RETURN ( __MKULARGEINT(ul) );
 # endif
-		}
-		break;
-
-	    case __MASKSMALLINT(SLONGARRAY):
-		/*
-		 * signed 32bit ints
-		 */
-		/* Notice: the hard coded shifts are by purpose;
-		 * it makes us independent of the int-size of the machine
-		 */
-		if ((unsigned)indx < (nbytes>>2)) {
-		    int32 *slp;
-		    int32 l;
-
-		    slp = (int32 *)(pFirst + (indx<<2));
-		    l = *slp;
+                }
+                break;
+
+            case __MASKSMALLINT(SLONGARRAY):
+                /*
+                 * signed 32bit ints
+                 */
+                /* Notice: the hard coded shifts are by purpose;
+                 * it makes us independent of the int-size of the machine
+                 */
+                if ((unsigned)indx < (nbytes>>2)) {
+                    int32 *slp;
+                    int32 l;
+
+                    slp = (int32 *)(pFirst + (indx<<2));
+                    l = *slp;
 # if __POINTER_SIZE__ == 8
-		    {
-			INT ll = (INT)l;
-			RETURN ( __mkSmallInteger(ll) );
-		    }
+                    {
+                        INT ll = (INT)l;
+                        RETURN ( __mkSmallInteger(ll) );
+                    }
 # else
-		    if (__ISVALIDINTEGER(l)) {
-			RETURN ( __mkSmallInteger(l) );
-		    }
-		    RETURN ( __MKLARGEINT(l) );
+                    if (__ISVALIDINTEGER(l)) {
+                        RETURN ( __mkSmallInteger(l) );
+                    }
+                    RETURN ( __MKLARGEINT(l) );
 # endif
-		}
-		break;
-
-	    case __MASKSMALLINT(SLONGLONGARRAY):
-		/*
-		 * signed 64bit longlongs
-		 */
+                }
+                break;
+
+            case __MASKSMALLINT(SLONGLONGARRAY):
+                /*
+                 * signed 64bit longlongs
+                 */
 # ifdef __NEED_LONGLONG_ALIGN
-		if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
-		    int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
-
-		    pFirst += delta;
-		    nbytes -= delta;
-		}
+                if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
+                    int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
+
+                    pFirst += delta;
+                    nbytes -= delta;
+                }
 # endif
-		/* Notice: the hard coded shifts are by purpose;
-		 * it makes us independent of the long/longlong-size of the machine
-		 */
-		if ((unsigned)indx < (nbytes>>3)) {
+                /* Notice: the hard coded shifts are by purpose;
+                 * it makes us independent of the long/longlong-size of the machine
+                 */
+                if ((unsigned)indx < (nbytes>>3)) {
 # if __POINTER_SIZE__ == 8
-		    INT *slp, ll;
-
-		    slp = (INT *)(pFirst + (indx<<3));
-		    ll = *slp;
-		    if (__ISVALIDINTEGER(ll)) {
-			RETURN ( __mkSmallInteger(ll) );
-		    }
-		    RETURN ( __MKLARGEINT(ll) );
+                    INT *slp, ll;
+
+                    slp = (INT *)(pFirst + (indx<<3));
+                    ll = *slp;
+                    if (__ISVALIDINTEGER(ll)) {
+                        RETURN ( __mkSmallInteger(ll) );
+                    }
+                    RETURN ( __MKLARGEINT(ll) );
 # else
-		    __int64__ *llp;
-
-		    llp = (__int64__ *)(pFirst + (indx<<3));
-		    RETURN (__MKINT64(llp));
+                    __int64__ *llp;
+
+                    llp = (__int64__ *)(pFirst + (indx<<3));
+                    RETURN (__MKINT64(llp));
 # endif
-		}
-		break;
-
-	    case __MASKSMALLINT(LONGLONGARRAY):
-		/*
-		 * unsigned 64bit longlongs
-		 */
+                }
+                break;
+
+            case __MASKSMALLINT(LONGLONGARRAY):
+                /*
+                 * unsigned 64bit longlongs
+                 */
 # ifdef __NEED_LONGLONG_ALIGN
-		if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
-		    int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
-
-		    pFirst += delta;
-		    nbytes -= delta;
-		}
+                if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
+                    int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
+
+                    pFirst += delta;
+                    nbytes -= delta;
+                }
 # endif
-		/* Notice: the hard coded shifts are by purpose;
-		 * it makes us independent of the long/longlong-size of the machine
-		 */
-		if ((unsigned)indx < (nbytes>>3)) {
+                /* Notice: the hard coded shifts are by purpose;
+                 * it makes us independent of the long/longlong-size of the machine
+                 */
+                if ((unsigned)indx < (nbytes>>3)) {
 # if __POINTER_SIZE__ == 8
-		    unsigned INT *ulp, ul;
-
-		    ulp = (unsigned INT *)(pFirst + (indx<<3));
-		    ul = *ulp;
-		    if (ul <= _MAX_INT) {
-			RETURN ( __mkSmallInteger(ul) );
-		    }
-		    RETURN ( __MKULARGEINT(ul) );
+                    unsigned INT *ulp, ul;
+
+                    ulp = (unsigned INT *)(pFirst + (indx<<3));
+                    ul = *ulp;
+                    if (ul <= _MAX_INT) {
+                        RETURN ( __mkSmallInteger(ul) );
+                    }
+                    RETURN ( __MKULARGEINT(ul) );
 # else
-		    __uint64__ *llp;
-
-		    llp = (__uint64__ *)(pFirst + (indx<<3));
-		    RETURN (__MKUINT64(llp));
+                    __uint64__ *llp;
+
+                    llp = (__uint64__ *)(pFirst + (indx<<3));
+                    RETURN (__MKUINT64(llp));
 # endif
-		}
-		break;
-	}
+                }
+                break;
+        }
     }
 #endif /* ! __SCHTEAM__ */
 %}.
@@ -1090,10 +1090,10 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     {
-	int idx1Based = index.intValue();   // st index is 1 based
-
-	self.basicAt_put(idx1Based, anObject );
-	return context._RETURN( anObject );
+        int idx1Based = index.intValue();   // st index is 1 based
+
+        self.basicAt_put(idx1Based, anObject );
+        return context._RETURN( anObject );
     }
     /* NOTREACHED */
 #else
@@ -1110,300 +1110,300 @@
        and SmallInteger */
 
     if (__isSmallInteger(index)) {
-	indx = __intVal(index) - 1;
-	myClass = __qClass(self);
-	n /* ninstvars */ = __intVal(__ClassInstPtr(myClass)->c_ninstvars);
-	n /* nInstBytes */ = OHDR_SIZE + __OBJS2BYTES__(n /* ninstvars */);
-	nbytes = __qSize(self) - n /* nInstBytes */;
-	pFirst = (char *)(__InstPtr(self)) + n /* nInstBytes */;
-
-	switch ((INT)(__ClassInstPtr(myClass)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
-	    case __MASKSMALLINT(POINTERARRAY):
-		if ((unsigned)indx < (__BYTES2OBJS__(nbytes))) {
-		    OBJ *op;
-
-		    op = (OBJ *)pFirst + indx;
-		    *op = anObject;
-		    __STORE(self, anObject);
-		    RETURN ( anObject );
-		}
-		break;
-
-	    case __MASKSMALLINT(WKPOINTERARRAY):
-		if ((unsigned)indx < (__BYTES2OBJS__(nbytes))) {
-		    OBJ *op;
-
-		    op = (OBJ *)pFirst + indx;
-		    *op = anObject;
-		    __STORE(self, anObject);
-		    __WEAK_WRITE__(self, anObject);
-		    RETURN ( anObject );
-		}
-		break;
-
-	    case __MASKSMALLINT(BYTEARRAY):
-		if (__isSmallInteger(anObject)) {
-		    val = __intVal(anObject);
-		    if ((val & ~0xFF) == 0 /* i.e. (val >= 0) && (val <= 255) */) {
-			if ((unsigned)indx < nbytes) {
-			    char *cp;
-
-			    cp = pFirst + indx;
-			    *cp = val;
-			    RETURN ( anObject );
-			}
-		    }
-		}
-		break;
-
-	    case __MASKSMALLINT(FLOATARRAY):
+        indx = __intVal(index) - 1;
+        myClass = __qClass(self);
+        n /* ninstvars */ = __intVal(__ClassInstPtr(myClass)->c_ninstvars);
+        n /* nInstBytes */ = OHDR_SIZE + __OBJS2BYTES__(n /* ninstvars */);
+        nbytes = __qSize(self) - n /* nInstBytes */;
+        pFirst = (char *)(__InstPtr(self)) + n /* nInstBytes */;
+
+        switch ((INT)(__ClassInstPtr(myClass)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
+            case __MASKSMALLINT(POINTERARRAY):
+                if ((unsigned)indx < (__BYTES2OBJS__(nbytes))) {
+                    OBJ *op;
+
+                    op = (OBJ *)pFirst + indx;
+                    *op = anObject;
+                    __STORE(self, anObject);
+                    RETURN ( anObject );
+                }
+                break;
+
+            case __MASKSMALLINT(WKPOINTERARRAY):
+                if ((unsigned)indx < (__BYTES2OBJS__(nbytes))) {
+                    OBJ *op;
+
+                    op = (OBJ *)pFirst + indx;
+                    *op = anObject;
+                    __STORE(self, anObject);
+                    __WEAK_WRITE__(self, anObject);
+                    RETURN ( anObject );
+                }
+                break;
+
+            case __MASKSMALLINT(BYTEARRAY):
+                if (__isSmallInteger(anObject)) {
+                    val = __intVal(anObject);
+                    if ((val & ~0xFF) == 0 /* i.e. (val >= 0) && (val <= 255) */) {
+                        if ((unsigned)indx < nbytes) {
+                            char *cp;
+
+                            cp = pFirst + indx;
+                            *cp = val;
+                            RETURN ( anObject );
+                        }
+                    }
+                }
+                break;
+
+            case __MASKSMALLINT(FLOATARRAY):
 # ifdef __NEED_FLOATARRAY_ALIGN
-		if ((INT)pFirst & (__FLOATARRAY_ALIGN-1)) {
-		    int delta = __FLOATARRAY_ALIGN - ((INT)pFirst & (__FLOATARRAY_ALIGN-1));
-
-		    pFirst += delta;
-		    nbytes -= delta;
-		}
+                if ((INT)pFirst & (__FLOATARRAY_ALIGN-1)) {
+                    int delta = __FLOATARRAY_ALIGN - ((INT)pFirst & (__FLOATARRAY_ALIGN-1));
+
+                    pFirst += delta;
+                    nbytes -= delta;
+                }
 # endif
-		if ((unsigned)indx < (nbytes / sizeof(float))) {
-		    float *fp;
-
-		    fp = (float *)pFirst + indx;
-		    if (anObject != nil) {
-			if (! __isSmallInteger(anObject)) {
-			    if (__qIsFloatLike(anObject)) {
-				*fp = (float)(__floatVal(anObject));
-				RETURN ( anObject );
-			    }
-			    if (__qIsShortFloat(anObject)) {
-				*fp = __shortFloatVal(anObject);
-				RETURN ( anObject );
-			    }
-			} else {
-			    *fp = (float) __intVal(anObject);
-			    RETURN ( anObject );
-			}
-		    }
-		}
-		break;
-
-	    case __MASKSMALLINT(DOUBLEARRAY):
+                if ((unsigned)indx < (nbytes / sizeof(float))) {
+                    float *fp;
+
+                    fp = (float *)pFirst + indx;
+                    if (anObject != nil) {
+                        if (! __isSmallInteger(anObject)) {
+                            if (__qIsFloatLike(anObject)) {
+                                *fp = (float)(__floatVal(anObject));
+                                RETURN ( anObject );
+                            }
+                            if (__qIsShortFloat(anObject)) {
+                                *fp = __shortFloatVal(anObject);
+                                RETURN ( anObject );
+                            }
+                        } else {
+                            *fp = (float) __intVal(anObject);
+                            RETURN ( anObject );
+                        }
+                    }
+                }
+                break;
+
+            case __MASKSMALLINT(DOUBLEARRAY):
 # ifdef __NEED_DOUBLE_ALIGN
-		if ((INT)pFirst & (__DOUBLE_ALIGN-1)) {
-		    int delta = __DOUBLE_ALIGN - ((INT)pFirst & (__DOUBLE_ALIGN-1));
-
-		    pFirst += delta;
-		    nbytes -= delta;
-		}
+                if ((INT)pFirst & (__DOUBLE_ALIGN-1)) {
+                    int delta = __DOUBLE_ALIGN - ((INT)pFirst & (__DOUBLE_ALIGN-1));
+
+                    pFirst += delta;
+                    nbytes -= delta;
+                }
 # endif
-		if ((unsigned)indx < (nbytes / sizeof(double))) {
-		    double *dp;
-
-		    dp = (double *)pFirst + indx;
-		    if (anObject != nil) {
-			if (! __isSmallInteger(anObject)) {
-			    if (__qIsFloatLike(anObject)) {
-				*dp = __floatVal(anObject);
-				RETURN ( anObject );
-			    }
-			    if (__qIsShortFloat(anObject)) {
-				*dp = (double)__shortFloatVal(anObject);
-				RETURN ( anObject );
-			    }
-			} else {
-			    *dp = (double) __intVal(anObject);
-			    RETURN ( anObject );
-			}
-		    }
-		}
-		break;
-
-	    case __MASKSMALLINT(WORDARRAY):
-		if (__isSmallInteger(anObject)) {
-		    val = __intVal(anObject);
-		    if ((unsigned)val <= 0xFFFF) {
-			if ((unsigned)indx < (nbytes>>1)) {
-			    unsigned short *sp;
-
-			    sp = (unsigned short *)(pFirst + (indx<<1));
-			    *sp = val;
-			    RETURN ( anObject );
-			}
-		    }
-		}
-		break;
-
-	    case __MASKSMALLINT(SWORDARRAY):
-		if (__isSmallInteger(anObject)) {
-		    val = __intVal(anObject);
-		    if ((val >= -32768) && (val < 32768)) {
-			if ((unsigned)indx < (nbytes>>1)) {
-			    short *ssp;
-
-			    ssp = (short *)(pFirst + (indx<<1));
-			    *ssp = val;
-			    RETURN ( anObject );
-			}
-		    }
-		}
-		break;
-
-	    case __MASKSMALLINT(SLONGARRAY):
-		if ((unsigned)indx < (nbytes>>2)) {
-		    int32 *slp;
-
-		    slp = (int32 *)(pFirst + (indx<<2));
-		    if (__isSmallInteger(anObject)) {
-			*slp = __intVal(anObject);
-			RETURN ( anObject );
-		    }
-		    n = __signedLongIntVal(anObject);
-		    /*
-		     * zero means failure for an int larger than INT-size bytes
-		     * (would be a smallInteger)
-		     */
-		    if (n) {
+                if ((unsigned)indx < (nbytes / sizeof(double))) {
+                    double *dp;
+
+                    dp = (double *)pFirst + indx;
+                    if (anObject != nil) {
+                        if (! __isSmallInteger(anObject)) {
+                            if (__qIsFloatLike(anObject)) {
+                                *dp = __floatVal(anObject);
+                                RETURN ( anObject );
+                            }
+                            if (__qIsShortFloat(anObject)) {
+                                *dp = (double)__shortFloatVal(anObject);
+                                RETURN ( anObject );
+                            }
+                        } else {
+                            *dp = (double) __intVal(anObject);
+                            RETURN ( anObject );
+                        }
+                    }
+                }
+                break;
+
+            case __MASKSMALLINT(WORDARRAY):
+                if (__isSmallInteger(anObject)) {
+                    val = __intVal(anObject);
+                    if ((unsigned)val <= 0xFFFF) {
+                        if ((unsigned)indx < (nbytes>>1)) {
+                            unsigned short *sp;
+
+                            sp = (unsigned short *)(pFirst + (indx<<1));
+                            *sp = val;
+                            RETURN ( anObject );
+                        }
+                    }
+                }
+                break;
+
+            case __MASKSMALLINT(SWORDARRAY):
+                if (__isSmallInteger(anObject)) {
+                    val = __intVal(anObject);
+                    if ((val >= -32768) && (val < 32768)) {
+                        if ((unsigned)indx < (nbytes>>1)) {
+                            short *ssp;
+
+                            ssp = (short *)(pFirst + (indx<<1));
+                            *ssp = val;
+                            RETURN ( anObject );
+                        }
+                    }
+                }
+                break;
+
+            case __MASKSMALLINT(SLONGARRAY):
+                if ((unsigned)indx < (nbytes>>2)) {
+                    int32 *slp;
+
+                    slp = (int32 *)(pFirst + (indx<<2));
+                    if (__isSmallInteger(anObject)) {
+                        *slp = __intVal(anObject);
+                        RETURN ( anObject );
+                    }
+                    n = __signedLongIntVal(anObject);
+                    /*
+                     * zero means failure for an int larger than INT-size bytes
+                     * (would be a smallInteger)
+                     */
+                    if (n) {
 # if __POINTER_SIZE__ == 8
-			if ((n >= -0x80000000) && (n < 0x80000000))
+                        if ((n >= -0x80000000) && (n < 0x80000000))
 # endif
-			{
-			    *slp = n;
-			    RETURN ( anObject );
-			}
-		    }
-		}
-		break;
-
-	    case __MASKSMALLINT(LONGARRAY):
-		if ((unsigned)indx < (nbytes>>2)) {
-		    unsigned int32 *lp;
-
-		    lp = (unsigned int32 *)(pFirst + (indx<<2));
-		    if (anObject == __mkSmallInteger(0)) {
-			*lp = 0;
-			RETURN ( anObject );
-		    }
-		    u = __longIntVal(anObject);
-		    /*
-		     * zero means failure for an int larger than 4 bytes
-		     * (would be a smallInteger)
-		     */
-		    if (u) {
+                        {
+                            *slp = n;
+                            RETURN ( anObject );
+                        }
+                    }
+                }
+                break;
+
+            case __MASKSMALLINT(LONGARRAY):
+                if ((unsigned)indx < (nbytes>>2)) {
+                    unsigned int32 *lp;
+
+                    lp = (unsigned int32 *)(pFirst + (indx<<2));
+                    if (anObject == __mkSmallInteger(0)) {
+                        *lp = 0;
+                        RETURN ( anObject );
+                    }
+                    u = __longIntVal(anObject);
+                    /*
+                     * zero means failure for an int larger than 4 bytes
+                     * (would be a smallInteger)
+                     */
+                    if (u) {
 # if __POINTER_SIZE__ == 8
-			if (u <= 0xFFFFFFFF)
+                        if (u <= 0xFFFFFFFF)
 # endif
-			{
-			    *lp = u;
-			    RETURN ( anObject );
-			}
-		    }
-		}
-		break;
-
-	    case __MASKSMALLINT(SLONGLONGARRAY):
+                        {
+                            *lp = u;
+                            RETURN ( anObject );
+                        }
+                    }
+                }
+                break;
+
+            case __MASKSMALLINT(SLONGLONGARRAY):
 # ifdef __NEED_LONGLONG_ALIGN
-		if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
-		    int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
-
-		    pFirst += delta;
-		    nbytes -= delta;
-		}
+                if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
+                    int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
+
+                    pFirst += delta;
+                    nbytes -= delta;
+                }
 # endif
-		if ((unsigned)indx < (nbytes>>3)) {
-		    __int64__ ll;
-		    __int64__ *sllp;
-
-		    sllp = (__int64__ *)(pFirst + (indx<<3));
+                if ((unsigned)indx < (nbytes>>3)) {
+                    __int64__ ll;
+                    __int64__ *sllp;
+
+                    sllp = (__int64__ *)(pFirst + (indx<<3));
 
 # if __POINTER_SIZE__ == 8
-		    if (__isSmallInteger(anObject)) {
-			*sllp = __intVal(anObject);
-			RETURN ( anObject );
-		    }
-		    n = __signedLongIntVal(anObject);
-		    if (n) {
-			*sllp = n;
-			RETURN ( anObject );
-		    }
+                    if (__isSmallInteger(anObject)) {
+                        *sllp = __intVal(anObject);
+                        RETURN ( anObject );
+                    }
+                    n = __signedLongIntVal(anObject);
+                    if (n) {
+                        *sllp = n;
+                        RETURN ( anObject );
+                    }
 # else
-		    if (anObject == __mkSmallInteger(0)) {
-			ll.lo = ll.hi = 0;
-			*sllp = ll;
-			RETURN ( anObject );
-		    }
-		    if (__signedLong64IntVal(anObject, &ll)) {
-			*sllp = ll;
-			RETURN ( anObject );
-		    }
+                    if (anObject == __mkSmallInteger(0)) {
+                        ll.lo = ll.hi = 0;
+                        *sllp = ll;
+                        RETURN ( anObject );
+                    }
+                    if (__signedLong64IntVal(anObject, &ll)) {
+                        *sllp = ll;
+                        RETURN ( anObject );
+                    }
 # endif
-		}
-		break;
-
-	    case __MASKSMALLINT(LONGLONGARRAY):
+                }
+                break;
+
+            case __MASKSMALLINT(LONGLONGARRAY):
 # ifdef __NEED_LONGLONG_ALIGN
-		if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
-		    int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
-
-		    pFirst += delta;
-		    nbytes -= delta;
-		}
+                if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
+                    int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
+
+                    pFirst += delta;
+                    nbytes -= delta;
+                }
 # endif
-		if ((unsigned)indx < (nbytes>>3)) {
-		    __uint64__ ll;
-		    __uint64__ *llp;
-
-		    llp = (__uint64__ *)(pFirst + (indx<<3));
+                if ((unsigned)indx < (nbytes>>3)) {
+                    __uint64__ ll;
+                    __uint64__ *llp;
+
+                    llp = (__uint64__ *)(pFirst + (indx<<3));
 # if __POINTER_SIZE__ == 8
-		    if (__isSmallInteger(anObject)) {
-			*llp = __intVal(anObject);
-			RETURN ( anObject );
-		    }
-		    ll = __longIntVal(anObject);
-		    if (ll) {
-			*llp = ll;
-			RETURN ( anObject );
-		    }
+                    if (__isSmallInteger(anObject)) {
+                        *llp = __intVal(anObject);
+                        RETURN ( anObject );
+                    }
+                    ll = __longIntVal(anObject);
+                    if (ll) {
+                        *llp = ll;
+                        RETURN ( anObject );
+                    }
 # else
-		    if (anObject == __mkSmallInteger(0)) {
-			ll.lo = ll.hi = 0;
-			*llp = ll;
-			RETURN ( anObject );
-		    }
-		    if (__unsignedLong64IntVal(anObject, &ll)) {
-			*llp = ll;
-			RETURN ( anObject );
-		    }
+                    if (anObject == __mkSmallInteger(0)) {
+                        ll.lo = ll.hi = 0;
+                        *llp = ll;
+                        RETURN ( anObject );
+                    }
+                    if (__unsignedLong64IntVal(anObject, &ll)) {
+                        *llp = ll;
+                        RETURN ( anObject );
+                    }
 # endif
-		}
-		break;
-	}
+                }
+                break;
+        }
     }
 #endif /* ! __SCHTEAM__ */
 %}.
     index isInteger ifFalse:[
-	"
-	 the index should be an integer number
-	"
-	^ self indexNotInteger:index
+        "
+         the index should be an integer number
+        "
+        ^ self indexNotInteger:index
     ].
     (index between:1 and:self size) ifFalse:[
-	"
-	 the index is less than 1 or greater than the size of the
-	 receiver collection
-	"
-	^ self subscriptBoundsError:index
+        "
+         the index is less than 1 or greater than the size of the
+         receiver collection
+        "
+        ^ self subscriptBoundsError:index
     ].
     (self class isFloatsOrDoubles) ifTrue:[
-	anObject isNumber ifTrue:[
-	    ^ self basicAt:index put:(anObject asFloat)
-	]
+        anObject isNumber ifTrue:[
+            ^ self basicAt:index put:(anObject asFloat)
+        ]
     ].
     anObject isInteger ifFalse:[
-	"
-	 the object to put into the receiver collection
-	 should be an integer number
-	"
-	^ self elementNotInteger
+        "
+         the object to put into the receiver collection
+         should be an integer number
+        "
+        ^ self elementNotInteger
     ].
     "
      the object to put into the receiver collection
@@ -1426,61 +1426,61 @@
 %{  /* NOCONTEXT */
 
     if (__isSmallInteger(index)) {
-	OBJ slf = self;
-	if (__isNonNilObject(slf)) {
-	    OBJ cls = __qClass(slf);
-	    INT indx = __intVal(index) - 1;
-	    INT nIndex = __byteArraySize(slf);
-	    unsigned char *pFirst = __byteArrayVal(slf) + __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-
-	    switch ((INT)(__ClassInstPtr(cls)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
-		case __MASKSMALLINT(DOUBLEARRAY):
+        OBJ slf = self;
+        if (__isNonNilObject(slf)) {
+            OBJ cls = __qClass(slf);
+            INT indx = __intVal(index) - 1;
+            INT nIndex = __byteArraySize(slf);
+            unsigned char *pFirst = __byteArrayVal(slf) + __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+
+            switch ((INT)(__ClassInstPtr(cls)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
+                case __MASKSMALLINT(DOUBLEARRAY):
 #ifdef __NEED_DOUBLE_ALIGN
-		    if ((INT)pFirst & (__DOUBLE_ALIGN-1)) {
-			int delta = __DOUBLE_ALIGN - ((INT)pFirst & (__DOUBLE_ALIGN-1));
-
-			pFirst += delta;
-			nIndex -= delta;
-		    }
+                    if ((INT)pFirst & (__DOUBLE_ALIGN-1)) {
+                        int delta = __DOUBLE_ALIGN - ((INT)pFirst & (__DOUBLE_ALIGN-1));
+
+                        pFirst += delta;
+                        nIndex -= delta;
+                    }
 #endif
-		    goto common;
-
-		case __MASKSMALLINT(FLOATARRAY):
+                    goto common;
+
+                case __MASKSMALLINT(FLOATARRAY):
 #ifdef __NEED_FLOATARRY_ALIGN
-		    if ((INT)pFirst & (__FLOATARRY_ALIGN-1)) {
-			int delta = __FLOATARRY_ALIGN - ((INT)pFirst & (__FLOATARRY_ALIGN-1));
-
-			pFirst += delta;
-			nIndex -= delta;
-		    }
+                    if ((INT)pFirst & (__FLOATARRY_ALIGN-1)) {
+                        int delta = __FLOATARRY_ALIGN - ((INT)pFirst & (__FLOATARRY_ALIGN-1));
+
+                        pFirst += delta;
+                        nIndex -= delta;
+                    }
 #endif
-		    goto common;
-
-		case __MASKSMALLINT(LONGLONGARRAY):
-		case __MASKSMALLINT(SLONGLONGARRAY):
+                    goto common;
+
+                case __MASKSMALLINT(LONGLONGARRAY):
+                case __MASKSMALLINT(SLONGLONGARRAY):
 #ifdef __NEED_LONGLONG_ALIGN
-		    if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
-			int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
-
-			pFirst += delta;
-			nIndex -= delta;
-		    }
+                    if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
+                        int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
+
+                        pFirst += delta;
+                        nIndex -= delta;
+                    }
 #endif
-		    goto common;
-
-		case __MASKSMALLINT(BYTEARRAY):
-		case __MASKSMALLINT(WORDARRAY):
-		case __MASKSMALLINT(LONGARRAY):
-		case __MASKSMALLINT(SWORDARRAY):
-		case __MASKSMALLINT(SLONGARRAY):
-	    common:
-		    if ((unsigned)indx < (unsigned)nIndex) {
-			RETURN ( __mkSmallInteger( (INT)(pFirst[indx])) );
-		    }
-		    break;
-
-	    }
-	}
+                    goto common;
+
+                case __MASKSMALLINT(BYTEARRAY):
+                case __MASKSMALLINT(WORDARRAY):
+                case __MASKSMALLINT(LONGARRAY):
+                case __MASKSMALLINT(SWORDARRAY):
+                case __MASKSMALLINT(SLONGARRAY):
+            common:
+                    if ((unsigned)indx < (unsigned)nIndex) {
+                        RETURN ( __mkSmallInteger( (INT)(pFirst[indx])) );
+                    }
+                    break;
+
+            }
+        }
     }
 %}.
     "/ index not integer or index out of range
@@ -1514,50 +1514,50 @@
     REGISTER OBJ cls;
 
     if (__bothSmallInteger(index, byteValue)) {
-	val = __intVal(byteValue);
-	if ((unsigned)(val) <= 0xFF /* i.e. (val >= 0) && (val <= 255) */) {
-	    slf = self;
-	    if (__isNonNilObject(slf)) {
-		int nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-		cls = __qClass(slf);
-
-		indx = __intVal(index) - 1;
-		switch ((INT)(__ClassInstPtr(cls)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
-		    case __MASKSMALLINT(DOUBLEARRAY):
+        val = __intVal(byteValue);
+        if ((unsigned)(val) <= 0xFF /* i.e. (val >= 0) && (val <= 255) */) {
+            slf = self;
+            if (__isNonNilObject(slf)) {
+                int nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+                cls = __qClass(slf);
+
+                indx = __intVal(index) - 1;
+                switch ((INT)(__ClassInstPtr(cls)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
+                    case __MASKSMALLINT(DOUBLEARRAY):
 # ifdef __NEED_DOUBLE_ALIGN
-			nInstBytes = (nInstBytes-1+__DOUBLE_ALIGN) &~ (__DOUBLE_ALIGN-1);
+                        nInstBytes = (nInstBytes-1+__DOUBLE_ALIGN) &~ (__DOUBLE_ALIGN-1);
 # endif
-			goto common;
-
-		    case __MASKSMALLINT(FLOATARRAY):
+                        goto common;
+
+                    case __MASKSMALLINT(FLOATARRAY):
 # ifdef __NEED_FLOATARRAY_ALIGN
-			nInstBytes = (nInstBytes-1+__FLOATARRAY_ALIGN) &~ (__FLOATARRAY_ALIGN-1);
+                        nInstBytes = (nInstBytes-1+__FLOATARRAY_ALIGN) &~ (__FLOATARRAY_ALIGN-1);
 # endif
-			goto common;
-
-		    case __MASKSMALLINT(LONGLONGARRAY):
-		    case __MASKSMALLINT(SLONGLONGARRAY):
+                        goto common;
+
+                    case __MASKSMALLINT(LONGLONGARRAY):
+                    case __MASKSMALLINT(SLONGLONGARRAY):
 # ifdef __NEED_LONGLONG_ALIGN
-			nInstBytes = (nInstBytes-1+__LONGLONG_ALIGN) &~ (__LONGLONG_ALIGN-1);
+                        nInstBytes = (nInstBytes-1+__LONGLONG_ALIGN) &~ (__LONGLONG_ALIGN-1);
 # endif
-			goto common;
-
-		    case __MASKSMALLINT(BYTEARRAY):
-		    case __MASKSMALLINT(WORDARRAY):
-		    case __MASKSMALLINT(LONGARRAY):
-		    case __MASKSMALLINT(SWORDARRAY):
-		    case __MASKSMALLINT(SLONGARRAY):
-		common:
-			indx += nInstBytes;
-			nIndex = __byteArraySize(slf);
-			if ((unsigned)indx < (unsigned)nIndex) {
-			    __ByteArrayInstPtr(slf)->ba_element[indx] = val;
-			    RETURN ( byteValue );
-			}
-			break;
-		}
-	    }
-	}
+                        goto common;
+
+                    case __MASKSMALLINT(BYTEARRAY):
+                    case __MASKSMALLINT(WORDARRAY):
+                    case __MASKSMALLINT(LONGARRAY):
+                    case __MASKSMALLINT(SWORDARRAY):
+                    case __MASKSMALLINT(SLONGARRAY):
+                common:
+                        indx += nInstBytes;
+                        nIndex = __byteArraySize(slf);
+                        if ((unsigned)indx < (unsigned)nIndex) {
+                            __ByteArrayInstPtr(slf)->ba_element[indx] = val;
+                            RETURN ( byteValue );
+                        }
+                        break;
+                }
+            }
+        }
     }
 %}.
     "/ index not integer or index out of range
@@ -1584,26 +1584,26 @@
     int idx, ninstvars;
 
     if (__isSmallInteger(index)) {
-	myClass = __Class(self);
-	idx = __intVal(index) - 1;
-	/*
-	 * do not allow returning of non-object fields.
-	 * if subclass did not make provisions for that,
-	 * we won't do so here ...
-	 */
-	if (((INT)(__ClassInstPtr(myClass)->c_flags) & __MASKSMALLINT(NONOBJECT_INSTS))) {
-	    if (idx == 0) {
-		RETURN ( nil )
-	    }
-	}
-	ninstvars = __intVal(__ClassInstPtr(myClass)->c_ninstvars);
-	if ((idx >= 0) && (idx < ninstvars)) {
-	    // do not trust the ninstvars slot - verify
-	    if ((__OBJS2BYTES__(ninstvars) + OHDR_SIZE) <= __qSize(self)) {
-		RETURN ( __InstPtr(self)->i_instvars[idx] );
-	    }
-	    console_printf("[VM] warning: bad ninsts in class\n");
-	}
+        myClass = __Class(self);
+        idx = __intVal(index) - 1;
+        /*
+         * do not allow returning of non-object fields.
+         * if subclass did not make provisions for that,
+         * we won't do so here ...
+         */
+        if (((INT)(__ClassInstPtr(myClass)->c_flags) & __MASKSMALLINT(NONOBJECT_INSTS))) {
+            if (idx == 0) {
+                RETURN ( nil )
+            }
+        }
+        ninstvars = __intVal(__ClassInstPtr(myClass)->c_ninstvars);
+        if ((idx >= 0) && (idx < ninstvars)) {
+            // do not trust the ninstvars slot - verify
+            if ((__OBJS2BYTES__(ninstvars) + OHDR_SIZE) <= __qSize(self)) {
+                RETURN ( __InstPtr(self)->i_instvars[idx] );
+            }
+            console_printf("[VM] warning: bad ninsts in class\n");
+        }
     }
 #endif /* not SCHTEAM */
 %}.
@@ -1624,28 +1624,28 @@
     int idx, ninstvars;
 
     if (__isSmallInteger(index)) {
-	myClass = __Class(self);
-	idx = __intVal(index) - 1;
-	ninstvars = __intVal(__ClassInstPtr(myClass)->c_ninstvars);
-	/*
-	 * do not allow setting of non-object fields.
-	 * if subclass did not make provisions for that,
-	 * we won't do so here ...
-	 */
-	if (((INT)(__ClassInstPtr(myClass)->c_flags) & __MASKSMALLINT(NONOBJECT_INSTS))) {
-	    if (idx == 0) {
-		RETURN ( nil )
-	    }
-	}
-	if ((idx >= 0) && (idx < ninstvars)) {
-	    // do not trust the ninstvars slot - verify
-	    if ((__OBJS2BYTES__(ninstvars) + OHDR_SIZE) <= __qSize(self)) {
-		__InstPtr(self)->i_instvars[idx] = value;
-		__STORE(self, value);
-		RETURN ( value );
-	    }
-	    console_printf("[VM] warning: bad ninsts in class\n");
-	}
+        myClass = __Class(self);
+        idx = __intVal(index) - 1;
+        ninstvars = __intVal(__ClassInstPtr(myClass)->c_ninstvars);
+        /*
+         * do not allow setting of non-object fields.
+         * if subclass did not make provisions for that,
+         * we won't do so here ...
+         */
+        if (((INT)(__ClassInstPtr(myClass)->c_flags) & __MASKSMALLINT(NONOBJECT_INSTS))) {
+            if (idx == 0) {
+                RETURN ( nil )
+            }
+        }
+        if ((idx >= 0) && (idx < ninstvars)) {
+            // do not trust the ninstvars slot - verify
+            if ((__OBJS2BYTES__(ninstvars) + OHDR_SIZE) <= __qSize(self)) {
+                __InstPtr(self)->i_instvars[idx] = value;
+                __STORE(self, value);
+                RETURN ( value );
+            }
+            console_printf("[VM] warning: bad ninsts in class\n");
+        }
     }
 #endif /* not SCHTEAM */
 %}.
@@ -1663,7 +1663,7 @@
 
     idx := self class instVarIndexFor:name.
     idx isNil ifTrue:[
-	^ self errorKeyNotFound:name.
+        ^ self errorKeyNotFound:name.
     ].
     ^ self instVarAt:idx.
 
@@ -1715,7 +1715,7 @@
 
     idx := self class instVarIndexFor:name.
     idx isNil ifTrue:[
-	^ self errorKeyNotFound:name.
+        ^ self errorKeyNotFound:name.
     ].
     ^ self instVarAt:idx put:value.
 
@@ -1767,17 +1767,17 @@
     int flags;
 
     if (!__isNonNilObject(self)) {
-	RETURN(self);
+        RETURN(self);
     }
     /*
      * bail out for special (weak) objects ..
      */
     flags = __intVal(__ClassInstPtr(__qClass(self))->c_flags);
     if (((flags & ~ARRAYMASK) == 0)
-	&& ((flags & ARRAYMASK) != WKPOINTERARRAY)
+        && ((flags & ARRAYMASK) != WKPOINTERARRAY)
     ) {
-	bzero((void *)__InstPtr(self)->i_instvars, __qSize(self)-OHDR_SIZE);
-	RETURN(self);
+        bzero((void *)__InstPtr(self)->i_instvars, __qSize(self)-OHDR_SIZE);
+        RETURN(self);
     }
 %}.
     "/ fail for special objects
@@ -1789,8 +1789,6 @@
     "
 ! !
 
-
-
 !Object methodsFor:'attributes access'!
 
 objectAttributeAt:attributeKey
@@ -1800,7 +1798,7 @@
 
     attrs := self objectAttributes.
     attrs size ~~ 0 ifTrue:[
-	^ attrs at:attributeKey ifAbsent:[]
+        ^ attrs at:attributeKey ifAbsent:[]
     ].
     ^ nil
 
@@ -1814,30 +1812,30 @@
     "/ must do this save from being reentered, since the attributes collection
     "/ is possibly accessed from multiple threads...
     ObjectAttributesAccessLock critical:[
-	| attrs |
-
-	attrs := self objectAttributes.
-	"/ only need a WeakIdentityDictionary, if there are any non-symbol keys in
-	"/ it. Start with a regular IDDict, and migrate to WeakIDDict if ever required.
-	"/ Typically, this never happens (but does in the UIPainter!!)
-	attrs isEmptyOrNil ifTrue:[
-	    attributeKey isSymbol ifTrue:[
-		attrs := IdentityDictionary new.
-	    ] ifFalse:[
-		attrs := WeakIdentityDictionary new.
-	    ].
-	    attrs at:attributeKey put:anObject.
-	    self objectAttributes:attrs.
-	] ifFalse:[
-	    attributeKey isSymbol ifFalse:[
-		attrs isWeakCollection ifFalse:[
-		    "first non-symbol attributeKey - convert to WeakIdentityDictionary"
-		    attrs := WeakIdentityDictionary new declareAllFrom:attrs.
-		    self objectAttributes:attrs.
-		].
-	    ].
-	    attrs at:attributeKey put:anObject.
-	].
+        | attrs |
+
+        attrs := self objectAttributes.
+        "/ only need a WeakIdentityDictionary, if there are any non-symbol keys in
+        "/ it. Start with a regular IDDict, and migrate to WeakIDDict if ever required.
+        "/ Typically, this never happens (but does in the UIPainter!!)
+        attrs isEmptyOrNil ifTrue:[
+            attributeKey isSymbol ifTrue:[
+                attrs := IdentityDictionary new.
+            ] ifFalse:[
+                attrs := WeakIdentityDictionary new.
+            ].
+            attrs at:attributeKey put:anObject.
+            self objectAttributes:attrs.
+        ] ifFalse:[
+            attributeKey isSymbol ifFalse:[
+                attrs isWeakCollection ifFalse:[
+                    "first non-symbol attributeKey - convert to WeakIdentityDictionary"
+                    attrs := WeakIdentityDictionary new declareAllFrom:attrs.
+                    self objectAttributes:attrs.
+                ].
+            ].
+            attrs at:attributeKey put:anObject.
+        ].
     ]
 
     "Attaching additional attributes (slots) to an arbitrary object:
@@ -1878,11 +1876,11 @@
     "/ is possibly accessed from multiple threads.
 
     ObjectAttributesAccessLock critical:[
-	aCollection isEmptyOrNil ifTrue:[
-	    ObjectAttributes removeKey:self ifAbsent:nil
-	] ifFalse:[
-	    ObjectAttributes at:self put:aCollection
-	].
+        aCollection isEmptyOrNil ifTrue:[
+            ObjectAttributes removeKey:self ifAbsent:nil
+        ] ifFalse:[
+            ObjectAttributes at:self put:aCollection
+        ].
     ]
 
     "Created: / 22.1.1998 / 21:29:35 / av"
@@ -1899,17 +1897,17 @@
     "/ must do this save from being reentered, since the attributes collection
     "/ is possibly accessed from multiple threads.
     ObjectAttributesAccessLock critical:[
-	|attrs|
-
-	attrs := self objectAttributes.
-	attrs notNil ifTrue:[
-	    attrs size ~~ 0 ifTrue:[
-		oldVal := attrs removeKey:attributeKey ifAbsent:nil.
-	    ].
-	    attrs size == 0 ifTrue:[
-		self objectAttributes:nil
-	    ].
-	]
+        |attrs|
+
+        attrs := self objectAttributes.
+        attrs notNil ifTrue:[
+            attrs size ~~ 0 ifTrue:[
+                oldVal := attrs removeKey:attributeKey ifAbsent:nil.
+            ].
+            attrs size == 0 ifTrue:[
+                self objectAttributes:nil
+            ].
+        ]
     ].
     ^ oldVal
 
@@ -1919,14 +1917,13 @@
 
 
 
-
 !Object methodsFor:'change & update'!
 
 broadcast:aSelectorSymbol
     "send a message with selector aSelectorSymbol to all my dependents"
 
     self dependentsDo:[:dependent |
-	dependent perform:aSelectorSymbol
+        dependent perform:aSelectorSymbol
     ]
 !
 
@@ -1935,7 +1932,7 @@
      argument anArgument to all my dependents."
 
     self dependentsDo:[:dependent |
-	dependent perform:aSelectorSymbol with:anArgument
+        dependent perform:aSelectorSymbol with:anArgument
     ]
 !
 
@@ -1944,7 +1941,7 @@
      grant the request, and return true if so"
 
     self dependentsDo:[:dependent |
-	dependent updateRequest ifFalse:[^ false].
+        dependent updateRequest ifFalse:[^ false].
     ].
     ^ true
 !
@@ -1954,7 +1951,7 @@
      grant the request, and return true if so"
 
     self dependentsDo:[:dependent |
-	(dependent updateRequest:aSymbol) ifFalse:[^ false].
+        (dependent updateRequest:aSymbol) ifFalse:[^ false].
     ].
     ^ true
 !
@@ -1982,9 +1979,9 @@
      about to send the change request."
 
     self dependentsDo:[:dependent |
-	dependent == anObject ifFalse:[
-	    (dependent updateRequest:aSymbol with:aParameter from:anObject) ifFalse:[^ false].
-	]
+        dependent == anObject ifFalse:[
+            (dependent updateRequest:aSymbol with:aParameter from:anObject) ifFalse:[^ false].
+        ]
     ].
     ^ true
 !
@@ -1996,9 +1993,9 @@
      about to send the change request."
 
     self dependentsDo:[:dependent |
-	dependent == anObject ifFalse:[
-	    (dependent updateRequest) ifFalse:[^ false].
-	]
+        dependent == anObject ifFalse:[
+            (dependent updateRequest) ifFalse:[^ false].
+        ]
     ].
     ^ true
 !
@@ -2025,7 +2022,7 @@
      and anArgument as arguments."
 
     self dependentsDo:[:dependent |
-	dependent update:aParameter with:anArgument from:self
+        dependent update:aParameter with:anArgument from:self
     ]
 !
 
@@ -2094,7 +2091,7 @@
 
     (self dependents includesIdentical:someone)
     ifFalse:[
-	^ aBlock value.
+        ^ aBlock value.
     ].
     self removeDependent:someone.
     ^ aBlock ensure:[ self addDependent:someone ]
@@ -2106,9 +2103,9 @@
 = anObject
     "return true if the receiver and the arg have the same structure.
      Notice:
-	This method is partially open coded (inlined) by the compiler(s)
-	identical objects are always considered equal.
-	redefining it may not work as expected."
+        This method is partially open coded (inlined) by the compiler(s)
+        identical objects are always considered equal.
+        redefining it may not work as expected."
 
     ^ self == anObject
 !
@@ -2117,8 +2114,8 @@
     "return true if the receiver and the arg are the same object.
      Never redefine this in any class.
      Notice:
-	This method is open coded (inlined) by the compiler(s)
-	- redefining it may not work as expected."
+        This method is open coded (inlined) by the compiler(s)
+        - redefining it may not work as expected."
 
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
@@ -2139,28 +2136,28 @@
 
     myClass := self class.
     myClass isVariable ifTrue:[
-	sz := self basicSize.
-
-	"compare the indexed variables"
-	1 to:sz do:[:i |
-	    val := self basicAt:i.
-	    val isLiteral ifTrue:[
-		val = (anObject basicAt:i) ifFalse:[^ false].
-	    ] ifFalse:[
-		(val deepSameContentsAs:(anObject basicAt:i)) ifFalse:[^ false].
-	    ]
-	]
+        sz := self basicSize.
+
+        "compare the indexed variables"
+        1 to:sz do:[:i |
+            val := self basicAt:i.
+            val isLiteral ifTrue:[
+                val = (anObject basicAt:i) ifFalse:[^ false].
+            ] ifFalse:[
+                (val deepSameContentsAs:(anObject basicAt:i)) ifFalse:[^ false].
+            ]
+        ]
     ].
 
     "compare the instance variables"
     sz := myClass instSize.
     1 to:sz do:[:i |
-	val := self instVarAt:i.
-	val isLiteral ifTrue:[
-	    val = (anObject instVarAt:i) ifFalse:[^ false].
-	] ifFalse:[
-	    (val deepSameContentsAs:(anObject instVarAt:i)) ifFalse:[^ false].
-	]
+        val := self instVarAt:i.
+        val isLiteral ifTrue:[
+            val = (anObject instVarAt:i) ifFalse:[^ false].
+        ] ifFalse:[
+            (val deepSameContentsAs:(anObject instVarAt:i)) ifFalse:[^ false].
+        ]
     ].
 
     ^ true
@@ -2199,25 +2196,25 @@
     static unsigned nextHash = 0;
 
     if (__isNonNilObject(self)) {
-	hash = __GET_HASH(self);
-	if (hash == 0) {
-	    /* has no hash yet */
-
-	    if (++nextHash > __MAX_HASH__) {
-		nextHash = 1;
-	    }
-	    hash = nextHash;
-	    __SET_HASH(self, hash);
-	}
-
-	/*
-	 * now, we got 11 bits for hashing;
-	 * make it as large as possible; since most hashers use the returned
-	 * key and take it modulo some prime number, this will allow for
-	 * better distribution (i.e. bigger empty spaces) in hashed collection.
-	 */
-	hash = __MAKE_HASH__(hash);
-	RETURN ( __mkSmallInteger(hash) );
+        hash = __GET_HASH(self);
+        if (hash == 0) {
+            /* has no hash yet */
+
+            if (++nextHash > __MAX_HASH__) {
+                nextHash = 1;
+            }
+            hash = nextHash;
+            __SET_HASH(self, hash);
+        }
+
+        /*
+         * now, we got 11 bits for hashing;
+         * make it as large as possible; since most hashers use the returned
+         * key and take it modulo some prime number, this will allow for
+         * better distribution (i.e. bigger empty spaces) in hashed collection.
+         */
+        hash = __MAKE_HASH__(hash);
+        RETURN ( __mkSmallInteger(hash) );
     }
 %}.
     ^ 0 "never reached, since redefined in UndefinedObject and SmallInteger"
@@ -2237,53 +2234,53 @@
     static unsigned INT nextClassHash = 0;
 
     if (__isNonNilObject(self)) {
-	/*
-	 * my own identityHash
-	 */
-	hash1 = __GET_HASH(self);
-	if (hash1 == 0) {
-	    /* has no hash yet */
-
-	    if (++nextHash > __MAX_HASH__) {
-		nextHash = 1;
-	    }
-	    hash1 = nextHash;
-	    __SET_HASH(self, hash1);
-	}
-	/*
-	 * my classes identityHash
-	 */
-	o = __qClass(self);
-	hash2 = __GET_HASH(o);
-	if (hash2 == 0) {
-	    /* has no hash yet */
-
-	    if (++nextClassHash > __MAX_HASH__) {
-		nextClassHash = 1;
-	    }
-	    hash2 = nextClassHash;
-	    __SET_HASH(o, hash2);
-	}
-
-	/*
-	 * some bits of my size
-	 */
-	sz = __qSize(self);
-
-	/*
-	 * now, we got 11 + 11 + 8 bits for hashing;
-	 * make it as large as possible; since most hashers use the returned
-	 * key and take it modulo some prime number, this will allow for
-	 * better distribution (i.e. bigger empty spaces) in hashed collection.
-	 */
-	hash = (hash1 << 11) | hash2;           /* 22 bits */
-	hash = (hash << 8) | (sz & 0xFC);       /* 30 bits */
-
-	while ((hash & 0x20000000) == 0) {
-	    hash <<= 1;
-	}
-
-	RETURN ( __mkSmallInteger(hash) );
+        /*
+         * my own identityHash
+         */
+        hash1 = __GET_HASH(self);
+        if (hash1 == 0) {
+            /* has no hash yet */
+
+            if (++nextHash > __MAX_HASH__) {
+                nextHash = 1;
+            }
+            hash1 = nextHash;
+            __SET_HASH(self, hash1);
+        }
+        /*
+         * my classes identityHash
+         */
+        o = __qClass(self);
+        hash2 = __GET_HASH(o);
+        if (hash2 == 0) {
+            /* has no hash yet */
+
+            if (++nextClassHash > __MAX_HASH__) {
+                nextClassHash = 1;
+            }
+            hash2 = nextClassHash;
+            __SET_HASH(o, hash2);
+        }
+
+        /*
+         * some bits of my size
+         */
+        sz = __qSize(self);
+
+        /*
+         * now, we got 11 + 11 + 8 bits for hashing;
+         * make it as large as possible; since most hashers use the returned
+         * key and take it modulo some prime number, this will allow for
+         * better distribution (i.e. bigger empty spaces) in hashed collection.
+         */
+        hash = (hash1 << 11) | hash2;           /* 22 bits */
+        hash = (hash << 8) | (sz & 0xFC);       /* 30 bits */
+
+        while ((hash & 0x20000000) == 0) {
+            hash <<= 1;
+        }
+
+        RETURN ( __mkSmallInteger(hash) );
     }
 %}.
     "never reached, since UndefinedObject and SmallInteger are not hashed upon in binary storage"
@@ -2302,13 +2299,13 @@
 
     myClass := self class.
     myClass isVariable ifTrue:[
-	sz := self basicSize.
-	anObject basicSize >= sz ifFalse:[^ false].
-
-	"compare the indexed variables"
-	1 to:sz do:[:i |
-	    (self basicAt:i) == (anObject basicAt:i) ifFalse:[^ false].
-	]
+        sz := self basicSize.
+        anObject basicSize >= sz ifFalse:[^ false].
+
+        "compare the indexed variables"
+        1 to:sz do:[:i |
+            (self basicAt:i) == (anObject basicAt:i) ifFalse:[^ false].
+        ]
     ].
 
     "compare the instance variables"
@@ -2316,7 +2313,7 @@
     anObject class instSize >= sz ifFalse:[^ false].
 
     1 to:sz do:[:i |
-	(self instVarAt:i) == (anObject instVarAt:i) ifFalse:[^ false].
+        (self instVarAt:i) == (anObject instVarAt:i) ifFalse:[^ false].
     ].
 
     ^ true
@@ -2333,9 +2330,9 @@
 ~= anObject
     "return true if the receiver and the arg do not have the same structure.
      Notice:
-	This method is partially open coded (inlined) by the compiler(s)
-	identical objects are never considered unequal.
-	redefining it may not work as expected."
+        This method is partially open coded (inlined) by the compiler(s)
+        identical objects are never considered unequal.
+        redefining it may not work as expected."
 
     ^ (self = anObject) not
 !
@@ -2344,8 +2341,8 @@
     "return true if the receiver and the arg are not the same object.
      Never redefine this in any class.
      Notice:
-	This method is open coded (inlined) by the compiler(s)
-	- redefining it may not work as expected."
+        This method is open coded (inlined) by the compiler(s)
+        - redefining it may not work as expected."
 
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
@@ -2444,24 +2441,24 @@
     "process the named instance variables"
     sz := myClass instSize.
     1 to:sz do:[:i |
-	t := anObject instVarAt:i.
-	aSymbol ~~ #yourself ifTrue:[
-	    t := t perform:aSymbol
-	].
-	self instVarAt:i put:t
+        t := anObject instVarAt:i.
+        aSymbol ~~ #yourself ifTrue:[
+            t := t perform:aSymbol
+        ].
+        self instVarAt:i put:t
     ].
 
     myClass isVariable ifTrue:[
-	sz := self basicSize.
-
-	"process the indexed instance variables"
-	1 to:sz do:[:i |
-	    t := anObject basicAt:i.
-	    aSymbol ~~ #yourself ifTrue:[
-		t := t perform:aSymbol.
-	    ].
-	    self basicAt:i put:t.
-	]
+        sz := self basicSize.
+
+        "process the indexed instance variables"
+        1 to:sz do:[:i |
+            t := anObject basicAt:i.
+            aSymbol ~~ #yourself ifTrue:[
+                t := t perform:aSymbol.
+            ].
+            self basicAt:i put:t.
+        ]
     ].
 !
 
@@ -2479,53 +2476,53 @@
     prototypesClass := aPrototype class.
     (myClass == prototypesClass
      or:[myClass isSubclassOf:prototypesClass]) ifTrue:[
-	"/ can do better, if my class is a subclass of the prototype's class
-	sz := prototypesClass instSize.
-	1 to: sz do:[:index |
-	    self instVarAt:index put:(aPrototype instVarAt:index)
-	]
+        "/ can do better, if my class is a subclass of the prototype's class
+        sz := prototypesClass instSize.
+        1 to: sz do:[:index |
+            self instVarAt:index put:(aPrototype instVarAt:index)
+        ]
     ] ifFalse:[
-	"/ map instvars by name
-	myInfo := myClass instanceVariableOffsets.
-	prototypesInfo := prototypesClass instanceVariableOffsets.
-	myInfo keysAndValuesDo:[:name :index | |varIndexAssoc|
-	    varIndexAssoc := prototypesInfo at:name ifAbsent:[].
-	    varIndexAssoc notNil ifTrue:[
-		self instVarAt:index put:(aPrototype instVarAt:(varIndexAssoc value))
-	    ]
-	]
+        "/ map instvars by name
+        myInfo := myClass instanceVariableOffsets.
+        prototypesInfo := prototypesClass instanceVariableOffsets.
+        myInfo keysAndValuesDo:[:name :index | |varIndexAssoc|
+            varIndexAssoc := prototypesInfo at:name ifAbsent:[].
+            varIndexAssoc notNil ifTrue:[
+                self instVarAt:index put:(aPrototype instVarAt:(varIndexAssoc value))
+            ]
+        ]
     ].
     myClass isVariable ifTrue:[
-	prototypesClass isVariable ifTrue:[
-	    sz := self basicSize min:aPrototype basicSize.
-	    1 to:sz do:[:index |
-		self basicAt:index put:(aPrototype basicAt:index)
-	    ].
-	].
+        prototypesClass isVariable ifTrue:[
+            sz := self basicSize min:aPrototype basicSize.
+            1 to:sz do:[:index |
+                self basicAt:index put:(aPrototype basicAt:index)
+            ].
+        ].
     ].
 
     "
      Class withoutUpdatingChangesDo:[
-	|point3D|
-
-	point3D := Point subclass:#Point3D
-	   instanceVariableNames:'z'
-	   classVariableNames:''
-	   poolDictionaries:''
-	   category:'testing'
-	   inEnvironment:nil.
-	 (point3D new cloneInstanceVariablesFrom:1@2) inspect.
+        |point3D|
+
+        point3D := Point subclass:#Point3D
+           instanceVariableNames:'z'
+           classVariableNames:''
+           poolDictionaries:''
+           category:'testing'
+           inEnvironment:nil.
+         (point3D new cloneInstanceVariablesFrom:1@2) inspect.
      ]
     "
 
     "
      Class withoutUpdatingChangesDo:[
-	 Point variableSubclass:#Point3D_test
-	   instanceVariableNames:'z'
-	   classVariableNames:''
-	   poolDictionaries:''
-	   category:'testing'.
-	 (((Smalltalk at:#Point3D_test) new:2) cloneInstanceVariablesFrom:#(1 2 3)) inspect.
+         Point variableSubclass:#Point3D_test
+           instanceVariableNames:'z'
+           classVariableNames:''
+           poolDictionaries:''
+           category:'testing'.
+         (((Smalltalk at:#Point3D_test) new:2) cloneInstanceVariablesFrom:#(1 2 3)) inspect.
      ]
     "
 
@@ -2533,19 +2530,19 @@
      |someObject|
 
      Class withoutUpdatingChangesDo:[
-	 Object subclass:#TestClass1
-	   instanceVariableNames:'foo bar'
-	   classVariableNames:''
-	   poolDictionaries:''
-	   category:'testing'.
-	 someObject := TestClass1 new.
-	 someObject instVarAt:1 put:'foo'; instVarAt:2 put:'bar'.
-	 Object subclass:#TestClass2
-	   instanceVariableNames:'bar foo'
-	   classVariableNames:''
-	   poolDictionaries:''
-	   category:'testing'.
-	 (TestClass2 new cloneInstanceVariablesFrom:someObject) inspect.
+         Object subclass:#TestClass1
+           instanceVariableNames:'foo bar'
+           classVariableNames:''
+           poolDictionaries:''
+           category:'testing'.
+         someObject := TestClass1 new.
+         someObject instVarAt:1 put:'foo'; instVarAt:2 put:'bar'.
+         Object subclass:#TestClass2
+           instanceVariableNames:'bar foo'
+           classVariableNames:''
+           poolDictionaries:''
+           category:'testing'.
+         (TestClass2 new cloneInstanceVariablesFrom:someObject) inspect.
      ]
     "
 
@@ -2575,8 +2572,8 @@
 copyToLevel:level
     "a controlled deepCopy, where the number of levels can be specified.
      Notice:
-	 This method DOES NOT handle cycles/self-refs and does NOT preserve object identity;
-	 i.e. identical references in the source are copied multiple times into the copy."
+         This method DOES NOT handle cycles/self-refs and does NOT preserve object identity;
+         i.e. identical references in the source are copied multiple times into the copy."
 
     |newObject newLevel class sz "{Class: SmallInteger}" newInst|
 
@@ -2590,22 +2587,22 @@
     "process the named instance variables"
     sz := class instSize.
     1 to:sz do:[:i |
-	newInst := newObject instVarAt:i.
-	newInst notNil ifTrue:[
-	    newObject instVarAt:i put:(newInst copyToLevel:newLevel).
-	].
+        newInst := newObject instVarAt:i.
+        newInst notNil ifTrue:[
+            newObject instVarAt:i put:(newInst copyToLevel:newLevel).
+        ].
     ].
 
     class isVariable ifTrue:[
-	sz := newObject basicSize.
-
-	"process the indexed instance variables"
-	1 to:sz do:[:i |
-	    newInst := newObject basicAt:i.
-	    newInst notNil ifTrue:[
-		newObject basicAt:i put:(newInst copyToLevel:newLevel).
-	    ].
-	]
+        sz := newObject basicSize.
+
+        "process the indexed instance variables"
+        1 to:sz do:[:i |
+            newInst := newObject basicAt:i.
+            newInst notNil ifTrue:[
+                newObject basicAt:i put:(newInst copyToLevel:newLevel).
+            ].
+        ]
     ].
     ^ newObject
 
@@ -2613,24 +2610,24 @@
      |a b|
 
      a := #(
-	    '1.1'
-	    '1.2'
-	    '1.3'
-	    (
-		'1.41'
-		'1.42'
-		'1.43'
-		    (
-			'1.441'
-			'1.442'
-			'1.443'
-			( '1.4441' '1.4442' '1.4443' )
-			'1.445'
-		    )
-		'1.45'
-	    )
-	    '1.5'
-	   ).
+            '1.1'
+            '1.2'
+            '1.3'
+            (
+                '1.41'
+                '1.42'
+                '1.43'
+                    (
+                        '1.441'
+                        '1.442'
+                        '1.443'
+                        ( '1.4441' '1.4442' '1.4443' )
+                        '1.445'
+                    )
+                '1.45'
+            )
+            '1.5'
+           ).
 
       b := a copyToLevel:1.
       self assert: ( (a at:1) == (b at:1) ).
@@ -2727,11 +2724,11 @@
 
     myClass := self class.
     myClass isVariable ifTrue:[
-	basicSize := self basicSize.
-	aCopy := self speciesForCopy basicNew:basicSize.
+        basicSize := self basicSize.
+        aCopy := self speciesForCopy basicNew:basicSize.
     ] ifFalse:[
-	basicSize := 0.
-	aCopy := self speciesForCopy basicNew
+        basicSize := 0.
+        aCopy := self speciesForCopy basicNew
     ].
     aCopy setHashFrom:self.
     aDictionary at:self put:aCopy.
@@ -2741,40 +2738,40 @@
     "
     instSize := myClass instSize.
     1 to:instSize do:[:i |
-	(self skipInstvarIndexInDeepCopy:i) ifFalse:[
-	    iOrig := self instVarAt:i.
-	    iOrig notNil ifTrue:[
-		iCopy := aDictionary at:iOrig ifAbsent:nil.
-		iCopy isNil ifTrue:[
-		    iCopy := iOrig deepCopyUsing:aDictionary postCopySelector:postCopySelector
-		].
-		aCopy instVarAt:i put:iCopy
-	    ]
-	]
+        (self skipInstvarIndexInDeepCopy:i) ifFalse:[
+            iOrig := self instVarAt:i.
+            iOrig notNil ifTrue:[
+                iCopy := aDictionary at:iOrig ifAbsent:nil.
+                iCopy isNil ifTrue:[
+                    iCopy := iOrig deepCopyUsing:aDictionary postCopySelector:postCopySelector
+                ].
+                aCopy instVarAt:i put:iCopy
+            ]
+        ]
     ].
 
     "
      copy indexed instvars - if any
     "
     basicSize ~~ 0 ifTrue:[
-	myClass isBits ifTrue:[
-	    "block-copy indexed instvars"
-	    aCopy replaceFrom:1 to:basicSize with:self startingAt:1
-	] ifFalse:[
-	    "individual deep copy the indexed variables"
-	    1 to:basicSize do:[:i |
-		iOrig := self basicAt:i.
-		iOrig notNil ifTrue:[
-		    "/ used to be dict-includesKey-ifTrue[dict-at:],
-		    "/ changed to use dict-at:ifAbsent:, to avoid double lookup in dictionary
-		    iCopy := aDictionary at:iOrig ifAbsent:nil.
-		    iCopy isNil ifTrue:[
-			iCopy := iOrig deepCopyUsing:aDictionary postCopySelector:postCopySelector
-		    ].
-		    aCopy basicAt:i put:iCopy
-		]
-	    ]
-	]
+        myClass isBits ifTrue:[
+            "block-copy indexed instvars"
+            aCopy replaceFrom:1 to:basicSize with:self startingAt:1
+        ] ifFalse:[
+            "individual deep copy the indexed variables"
+            1 to:basicSize do:[:i |
+                iOrig := self basicAt:i.
+                iOrig notNil ifTrue:[
+                    "/ used to be dict-includesKey-ifTrue[dict-at:],
+                    "/ changed to use dict-at:ifAbsent:, to avoid double lookup in dictionary
+                    iCopy := aDictionary at:iOrig ifAbsent:nil.
+                    iCopy isNil ifTrue:[
+                        iCopy := iOrig deepCopyUsing:aDictionary postCopySelector:postCopySelector
+                    ].
+                    aCopy basicAt:i put:iCopy
+                ]
+            ]
+        ]
     ].
 
     aCopy perform:postCopySelector withOptionalArgument:self and:aDictionary.
@@ -2813,9 +2810,9 @@
     REGISTER unsigned h;
 
     if (__isNonNilObject(self) && __isNonNilObject(anObject)) {
-	h = __GET_HASH(anObject);
-	__SET_HASH(self, h);
-	RETURN (self);
+        h = __GET_HASH(anObject);
+        __SET_HASH(self, h);
+        RETURN (self);
     }
 %}.
     self primitiveFailed    "neither receiver not arg may be nil or SmallInteger"
@@ -2840,54 +2837,54 @@
      */
     if (((flags & ~ARRAYMASK) == 0)
      && ((flags & ARRAYMASK) != WKPOINTERARRAY)) {
-	sz = __qSize(self);
-	__PROTECT__(self);
-	__qNew(theCopy, sz);    /* OBJECT ALLOCATION */
-	__UNPROTECT__(self);
-	if (theCopy) {
-	    cls = __qClass(self);
-	    spc = __qSpace(theCopy);
-
-	    theCopy->o_class = cls; __STORE_SPC(theCopy, cls, spc);
-
-	    sz = sz - OHDR_SIZE;
-	    if (sz) {
-		char *src, *dst;
-
-		src = (char *)(__InstPtr(self)->i_instvars);
-		dst = (char *)(__InstPtr(theCopy)->i_instvars);
+        sz = __qSize(self);
+        __PROTECT__(self);
+        __qNew(theCopy, sz);    /* OBJECT ALLOCATION */
+        __UNPROTECT__(self);
+        if (theCopy) {
+            cls = __qClass(self);
+            spc = __qSpace(theCopy);
+
+            theCopy->o_class = cls; __STORE_SPC(theCopy, cls, spc);
+
+            sz = sz - OHDR_SIZE;
+            if (sz) {
+                char *src, *dst;
+
+                src = (char *)(__InstPtr(self)->i_instvars);
+                dst = (char *)(__InstPtr(theCopy)->i_instvars);
 #ifdef bcopy4
-		{
-		    /* care for odd-number of longs */
-		    int nW = sz >> 2;
-
-		    if (sz & 3) {
-			nW++;
-		    }
-
-		    bcopy4(src, dst, nW);
-		}
+                {
+                    /* care for odd-number of longs */
+                    int nW = sz >> 2;
+
+                    if (sz & 3) {
+                        nW++;
+                    }
+
+                    bcopy4(src, dst, nW);
+                }
 #else
-		bcopy(src, dst, sz);
+                bcopy(src, dst, sz);
 #endif
 
-		flags &= ARRAYMASK;
-		if (flags == POINTERARRAY) {
-		    ninsts = __BYTES2OBJS__(sz);
-		} else {
-		    ninsts = __intVal(__ClassInstPtr(cls)->c_ninstvars);
-		}
-		if (ninsts) {
-		    do {
-			OBJ el;
-
-			el = __InstPtr(theCopy)->i_instvars[ninsts-1];
-			__STORE_SPC(theCopy, el, spc);
-		    } while (--ninsts);
-		}
-	    }
-	    RETURN (theCopy);
-	}
+                flags &= ARRAYMASK;
+                if (flags == POINTERARRAY) {
+                    ninsts = __BYTES2OBJS__(sz);
+                } else {
+                    ninsts = __intVal(__ClassInstPtr(cls)->c_ninstvars);
+                }
+                if (ninsts) {
+                    do {
+                        OBJ el;
+
+                        el = __InstPtr(theCopy)->i_instvars[ninsts-1];
+                        __STORE_SPC(theCopy, el, spc);
+                    } while (--ninsts);
+                }
+            }
+            RETURN (theCopy);
+        }
     }
 %}.
     "/ fallBack for special objects & memoryAllocation failure case
@@ -2907,9 +2904,9 @@
     |myClass aCopy|
 
     (myClass := self class) isVariable ifTrue:[
-	aCopy := myClass basicNew:(self basicSize).
+        aCopy := myClass basicNew:(self basicSize).
     ] ifFalse:[
-	aCopy := myClass basicNew
+        aCopy := myClass basicNew
     ].
 
     "copy the instance variables"
@@ -2942,9 +2939,9 @@
     |myClass aCopy|
 
     (myClass := self class) isVariable ifTrue:[
-	aCopy := myClass basicNew:(self basicSize).
+        aCopy := myClass basicNew:(self basicSize).
     ] ifFalse:[
-	aCopy := myClass basicNew
+        aCopy := myClass basicNew
     ].
 
     "copy the instance variables"
@@ -2966,11 +2963,11 @@
 
     "/ could still be a block or false.
     (aBooleanOrBlock value) ifFalse:[
-	AssertionFailedError
-	    raiseRequestWith:self
-	    errorString:('Assertion failed in ',
-			 thisContext methodHome sender printString,
-			 '[', thisContext  methodHome sender lineNumber printString,']')
+        AssertionFailedError
+            raiseRequestWith:self
+            errorString:('Assertion failed in ',
+                         thisContext methodHome sender printString,
+                         '[', thisContext  methodHome sender lineNumber printString,']')
     ].
 
     "
@@ -2992,9 +2989,9 @@
 
     "/ could still be a block or false.
     (aBooleanOrBlock value) ifFalse:[
-	AssertionFailedError
-	    raiseRequestWith:self
-	    errorString:(messageIfFailing, ' {',thisContext methodHome sender "methodHome" printString,' }')
+        AssertionFailedError
+            raiseRequestWith:self
+            errorString:(messageIfFailing, ' {',thisContext methodHome sender "methodHome" printString,' }')
     ].
 
     "
@@ -3027,12 +3024,12 @@
      this method should NOT be redefined in subclasses."
 
     Inspector isNil ifTrue:[
-	"
-	 for systems without GUI
-	"
-	self warn:'No Inspector defined (Inspector is nil).'
+        "
+         for systems without GUI
+        "
+        self warn:'No Inspector defined (Inspector is nil).'
     ] ifFalse:[
-	Inspector openOn:self
+        Inspector openOn:self
     ]
 
     "Modified: 18.5.1996 / 15:43:25 / cg"
@@ -3052,9 +3049,9 @@
 
     "/ dont send #breakPoint:info: here - ask cg why.
     (self isBreakPointEnabled:someKey) ifTrue:[
-	^ HaltSignal
-	    raiseRequestWith:someKey
-	    errorString:('Breakpoint encountered: %1' bindWith:someKey)
+        ^ HaltSignal
+            raiseRequestWith:someKey
+            errorString:('Breakpoint encountered: %1' bindWith:someKey)
     ].
 
     "
@@ -3082,9 +3079,9 @@
     <resource: #skipInDebuggersWalkBack>
 
     (self isBreakPointEnabled:someKey) ifTrue:[
-	^ HaltSignal
-	    raiseRequestWith:someKey
-	    errorString:(infoString bindWith:someKey)
+        ^ HaltSignal
+            raiseRequestWith:someKey
+            errorString:(infoString bindWith:someKey)
     ].
 !
 
@@ -3102,7 +3099,7 @@
     <resource: #skipInDebuggersWalkBack>
 
     (self isBreakPointEnabled:someKey) ifTrue:[
-	aBlock value
+        aBlock value
     ].
 
     "
@@ -3138,8 +3135,8 @@
     "{ Pragma: +optSpace }"
 
     EnabledBreakPoints notNil ifTrue:[
-	EnabledBreakPoints remove:someKey ifAbsent:[].
-	EnabledBreakPoints := EnabledBreakPoints asNilIfEmpty.
+        EnabledBreakPoints remove:someKey ifAbsent:[].
+        EnabledBreakPoints := EnabledBreakPoints asNilIfEmpty.
     ].
 
     "
@@ -3158,7 +3155,7 @@
     "{ Pragma: +optSpace }"
 
     EnabledBreakPoints isNil ifTrue:[
-	EnabledBreakPoints := Set new.
+        EnabledBreakPoints := Set new.
     ].
     EnabledBreakPoints add:someKey.
 
@@ -3186,7 +3183,7 @@
     ^ self
 
     "
-	(3 halt * 5)
+        (3 halt * 5)
     "
 
     "Modified: / 02-08-1999 / 17:00:29 / stefan"
@@ -3216,7 +3213,7 @@
 "/    something = OperatingSystem getLoginName ifTrue:[^ true].
 "/    something = 'testThis' ifTrue:[^ true].
     EncounteredBreakPoints notNil ifTrue:[
-	EncounteredBreakPoints add:someKey
+        EncounteredBreakPoints add:someKey
     ].
 
     ^ (EnabledBreakPoints notNil and:[ EnabledBreakPoints includes:someKey ])
@@ -3247,18 +3244,18 @@
     "for compatibility & debugging support:
      check if the receiver isKindOf:aClass and raise an error if not.
      Notice:
-	it is VERY questionable, if it makes sense to add manual
-	type checks to a dynamically typed language like smalltalk.
-	It will, at least, slow down performance,
-	make your code less reusable and clutter your code with stupid sends
-	of this selector. Also, read the comment in isKindOf:, regarding the
-	use of isXXX check methods.
+        it is VERY questionable, if it makes sense to add manual
+        type checks to a dynamically typed language like smalltalk.
+        It will, at least, slow down performance,
+        make your code less reusable and clutter your code with stupid sends
+        of this selector. Also, read the comment in isKindOf:, regarding the
+        use of isXXX check methods.
      You see: The author does not like this at all ..."
 
     <resource: #skipInDebuggersWalkBack>
 
     (self isKindOf:aClass) ifFalse:[
-	self error:'argument is not of expected type'
+        self error:'argument is not of expected type'
     ]
 !
 
@@ -3306,7 +3303,7 @@
     ('         called from ' , sender sender printString) infoPrintCR.
     ].
     message notNil ifTrue:[
-	'------>  ' infoPrint. message infoPrintCR
+        '------>  ' infoPrint. message infoPrintCR
     ]
 
     "
@@ -3351,8 +3348,8 @@
     |spec sender message|
 
     Smalltalk isSmalltalkDevelopmentSystem ifFalse:[
-	"ignore in production systems"
-	^ self.
+        "ignore in production systems"
+        ^ self.
     ].
 
     message := messageOrNil ? 'Obsolete method called'.
@@ -3363,28 +3360,28 @@
     ('         And may not be present in future ST/X versions.') infoPrintCR.
     ('         called from ' , sender printString) infoPrintCR.
     (sender selector startsWith:'perform:') ifTrue:[
-	sender := sender sender.
-	(sender selector startsWith:'perform:') ifTrue:[
-	    sender := sender sender.
-	].
-	('         called from ' , sender printString) infoPrintCR.
+        sender := sender sender.
+        (sender selector startsWith:'perform:') ifTrue:[
+            sender := sender sender.
+        ].
+        ('         called from ' , sender printString) infoPrintCR.
     ].
     message notNil ifTrue:[
-	'------>  ' infoPrint. message infoPrintCR
+        '------>  ' infoPrint. message infoPrintCR
     ].
 
     "CG: care for standalone non-GUI progs, which have no userPreferences class"
     (Smalltalk isInitialized
     and:[ UserPreferences notNil
     and:[ UserPreferences current haltInObsoleteMethod]]) ifTrue:[
-	"/ cg: nice try, stefan, but I don't want halts in system processes (fly by help and others)
-	Processor activeProcess isSystemProcess ifTrue:[
-	    (message , ' - please fix this now (no halt in system process)') infoPrintCR
-	] ifFalse:[
-	    "/ please check for the sender of the obsoleteMethodWarning,
-	    "/ and fix the code there.
-	    ObsoleteMethodCallWarning raiseRequestErrorString:(message , ' - please fix this now!!')
-	].
+        "/ cg: nice try, stefan, but I don't want halts in system processes (fly by help and others)
+        Processor activeProcess isSystemProcess ifTrue:[
+            (message , ' - please fix this now (no halt in system process)') infoPrintCR
+        ] ifFalse:[
+            "/ please check for the sender of the obsoleteMethodWarning,
+            "/ and fix the code there.
+            ObsoleteMethodCallWarning raiseRequestErrorString:(message , ' - please fix this now!!')
+        ].
     ].
 
     "
@@ -3404,9 +3401,9 @@
     "
      example:
 
-	...
-	self todo.
-	...
+        ...
+        self todo.
+        ...
     "
 !
 
@@ -3421,11 +3418,11 @@
     "
      example:
 
-	...
-	self todo:[
-	    code which needs more work ...
-	].
-	...
+        ...
+        self todo:[
+            code which needs more work ...
+        ].
+        ...
     "
 
     "Created: / 25-05-2007 / 21:34:39 / cg"
@@ -3443,10 +3440,10 @@
     "Example:   nil tracePoint:#stefan"
 
     (self isBreakPointEnabled:someKey) ifTrue:[
-	^ Transcript showCR:('Tracepoint (at %1 for %3 from %2)'
-				bindWith:(Timestamp now printString)
-				with:(thisContext sender printString)
-				with:someKey)
+        ^ Transcript showCR:('Tracepoint (at %1 for %3 from %2)'
+                                bindWith:(Timestamp now printString)
+                                with:(thisContext sender printString)
+                                with:someKey)
     ].
 
     "
@@ -3470,11 +3467,11 @@
     "Example:   nil tracePoint:#stefan"
 
     (self isBreakPointEnabled:someKey) ifTrue:[
-	Transcript showCR:('Tracepoint: %4 (at %1 for %3 from %2)'
-				bindWith:(Timestamp now printString)
-				with:(thisContext sender printString)
-				with:someKey
-				with:messageBlockOrString value)
+        Transcript showCR:('Tracepoint: %4 (at %1 for %3 from %2)'
+                                bindWith:(Timestamp now printString)
+                                with:(thisContext sender printString)
+                                with:someKey
+                                with:messageBlockOrString value)
     ].
 
     "
@@ -3502,35 +3499,35 @@
 
     wasBlocked := OperatingSystem blockInterrupts.
     [
-	|deps dep|
-
-	deps := self dependents.
-
-	"/ to save a fair amount of memory in case of
-	"/ many dependencies, we store a single dependent in
-	"/ a WeakArray, and switch to a WeakSet if more dependents are
-	"/ added.
-
-	(deps isNil or:[deps size == 0]) ifTrue:[
-	    self dependents:(WeakArray with:anObject)
-	] ifFalse:[
-	    deps class == WeakArray ifTrue:[
-		dep := deps at:1.
-		dep ~~ anObject ifTrue:[
-		    (dep isNil or:[dep class == SmallInteger]) ifTrue:[
-			deps at:1 put:anObject
-		    ] ifFalse:[
-			self dependents:(WeakIdentitySet with:dep with:anObject)
-		    ]
-		]
-	    ] ifFalse:[
-		deps add:anObject
-	    ]
-	]
+        |deps dep|
+
+        deps := self dependents.
+
+        "/ to save a fair amount of memory in case of
+        "/ many dependencies, we store a single dependent in
+        "/ a WeakArray, and switch to a WeakSet if more dependents are
+        "/ added.
+
+        (deps isNil or:[deps size == 0]) ifTrue:[
+            self dependents:(WeakArray with:anObject)
+        ] ifFalse:[
+            deps class == WeakArray ifTrue:[
+                dep := deps at:1.
+                dep ~~ anObject ifTrue:[
+                    (dep isNil or:[dep class == SmallInteger]) ifTrue:[
+                        deps at:1 put:anObject
+                    ] ifFalse:[
+                        self dependents:(WeakIdentitySet with:dep with:anObject)
+                    ]
+                ]
+            ] ifFalse:[
+                deps add:anObject
+            ]
+        ]
     ] ensure:[
-	wasBlocked ifFalse:[
-	    OperatingSystem unblockInterrupts
-	]
+        wasBlocked ifFalse:[
+            OperatingSystem unblockInterrupts
+        ]
     ]
 
     "Modified: / 27.10.1997 / 19:35:52 / cg"
@@ -3552,10 +3549,10 @@
 
     self breakDependents.
     1 to:self class instSize do:[:idx |
-	(self instVarAt:idx) breakDependentsRecursively.
+        (self instVarAt:idx) breakDependentsRecursively.
     ].
     1 to:self basicSize do:[:idx |
-	(self basicAt:idx) breakDependentsRecursively.
+        (self basicAt:idx) breakDependentsRecursively.
     ]
 !
 
@@ -3570,7 +3567,7 @@
     |deps|
 
     (deps := Dependencies at:self ifAbsent:nil) isNil ifTrue:[
-	^ #().
+        ^ #().
     ].
     ^ deps
 
@@ -3589,24 +3586,24 @@
     "/ faster execution (and to avoid creation of garbage blocks).
 
     (OperatingSystem blockInterrupts) ifTrue:[
-	"/ the common case - already blocked
-
-	(aCollection isNil or:[aCollection isEmpty]) ifTrue:[
-	    Dependencies removeKey:self ifAbsent:nil
-	] ifFalse:[
-	    Dependencies at:self put:aCollection
-	].
-	^ self
+        "/ the common case - already blocked
+
+        (aCollection isNil or:[aCollection isEmpty]) ifTrue:[
+            Dependencies removeKey:self ifAbsent:nil
+        ] ifFalse:[
+            Dependencies at:self put:aCollection
+        ].
+        ^ self
     ].
 
     [
-	(aCollection isNil or:[aCollection isEmpty]) ifTrue:[
-	    Dependencies removeKey:self ifAbsent:nil
-	] ifFalse:[
-	    Dependencies at:self put:aCollection
-	].
+        (aCollection isNil or:[aCollection isEmpty]) ifTrue:[
+            Dependencies removeKey:self ifAbsent:nil
+        ] ifFalse:[
+            Dependencies at:self put:aCollection
+        ].
     ] ensure:[
-	OperatingSystem unblockInterrupts
+        OperatingSystem unblockInterrupts
     ]
 
     "Modified: 30.1.1997 / 21:22:10 / cg"
@@ -3619,15 +3616,15 @@
 
     deps := self dependents.
     deps size ~~ 0 ifTrue:[
-	deps do:[:d |
-		    (d notNil and:[d class ~~ SmallInteger]) ifTrue:[
-			aBlock value:d
-		    ]
-		]
+        deps do:[:d |
+                    (d notNil and:[d class ~~ SmallInteger]) ifTrue:[
+                        aBlock value:d
+                    ]
+                ]
     ].
     nwDeps := self nonWeakDependents.
     (nwDeps ~~ deps and:[nwDeps size ~~ 0]) ifTrue:[
-	nwDeps do:aBlock
+        nwDeps do:aBlock
     ].
 
     "Modified: / 30.1.1998 / 14:03:40 / cg"
@@ -3660,43 +3657,43 @@
 
     wasBlocked := OperatingSystem blockInterrupts.
     [
-	|deps n d|
-
-	deps := self dependents.
-	deps size ~~ 0 ifTrue:[
-
-	    "/ to save a fair amount of memory in case of
-	    "/ many dependencies, we store a single dependent in
-	    "/ a WeakArray, and switch to a WeakSet if more dependents are
-	    "/ added. Here we have to do the inverse ...
-
-	    ((deps class == WeakArray) or:[deps class == Array]) ifTrue:[
-		((d := deps at:1) == anObject
-		or:[d isNil
-		or:[d class == SmallInteger]]) ifTrue:[
-		    self dependents:nil
-		]
-	    ] ifFalse:[
-		deps remove:anObject ifAbsent:[].
-		(n := deps size) == 0 ifTrue:[
-		    self dependents:nil
-		] ifFalse:[
-		    n == 1 ifTrue:[
-			d := deps firstIfEmpty:nil.
-			d notNil ifTrue:[
-			    deps := (deps isWeakCollection ifTrue:[WeakArray] ifFalse:[Array]) with:d
-			] ifFalse:[
-			    deps := nil
-			].
-			self dependents:deps.
-		    ]
-		]
-	    ]
-	]
+        |deps n d|
+
+        deps := self dependents.
+        deps size ~~ 0 ifTrue:[
+
+            "/ to save a fair amount of memory in case of
+            "/ many dependencies, we store a single dependent in
+            "/ a WeakArray, and switch to a WeakSet if more dependents are
+            "/ added. Here we have to do the inverse ...
+
+            ((deps class == WeakArray) or:[deps class == Array]) ifTrue:[
+                ((d := deps at:1) == anObject
+                or:[d isNil
+                or:[d class == SmallInteger]]) ifTrue:[
+                    self dependents:nil
+                ]
+            ] ifFalse:[
+                deps remove:anObject ifAbsent:[].
+                (n := deps size) == 0 ifTrue:[
+                    self dependents:nil
+                ] ifFalse:[
+                    n == 1 ifTrue:[
+                        d := deps firstIfEmpty:nil.
+                        d notNil ifTrue:[
+                            deps := (deps isWeakCollection ifTrue:[WeakArray] ifFalse:[Array]) with:d
+                        ] ifFalse:[
+                            deps := nil
+                        ].
+                        self dependents:deps.
+                    ]
+                ]
+            ]
+        ]
     ] ensure:[
-	wasBlocked ifFalse:[
-	    OperatingSystem unblockInterrupts
-	]
+        wasBlocked ifFalse:[
+            OperatingSystem unblockInterrupts
+        ]
     ]
 
     "Modified: / 05-07-2011 / 22:49:31 / cg"
@@ -3719,37 +3716,37 @@
 
     wasBlocked := OperatingSystem blockInterrupts.
     [
-	|deps dep|
-
-	deps := self nonWeakDependents.
-
-	"/ to save a fair amount of memory in case of
-	"/ many dependencies, we store a single dependent in
-	"/ an Array, and switch to a Set if more dependents are
-	"/ added.
-
-	deps size == 0 ifTrue:[
-	    anObject notNil ifTrue:[
-		self nonWeakDependents:(Array with:anObject).
-	    ] ifFalse:[
-		"adding nil causes problems when adding the next one
-		 (see below: trying to add nil to IdentitySet)"
+        |deps dep|
+
+        deps := self nonWeakDependents.
+
+        "/ to save a fair amount of memory in case of
+        "/ many dependencies, we store a single dependent in
+        "/ an Array, and switch to a Set if more dependents are
+        "/ added.
+
+        deps size == 0 ifTrue:[
+            anObject notNil ifTrue:[
+                self nonWeakDependents:(Array with:anObject).
+            ] ifFalse:[
+                "adding nil causes problems when adding the next one
+                 (see below: trying to add nil to IdentitySet)"
 "/                self halt:'try to add nil to list of dependents'.
-	    ].
-	] ifFalse:[
-	    deps class == Array ifTrue:[
-		dep := deps at:1.
-		dep ~~ anObject ifTrue:[
-		    self nonWeakDependents:(IdentitySet with:dep with:anObject)
-		]
-	    ] ifFalse:[
-		deps add:anObject
-	    ]
-	]
+            ].
+        ] ifFalse:[
+            deps class == Array ifTrue:[
+                dep := deps at:1.
+                dep ~~ anObject ifTrue:[
+                    self nonWeakDependents:(IdentitySet with:dep with:anObject)
+                ]
+            ] ifFalse:[
+                deps add:anObject
+            ]
+        ]
     ] ensure:[
-	wasBlocked ifFalse:[
-	    OperatingSystem unblockInterrupts
-	]
+        wasBlocked ifFalse:[
+            OperatingSystem unblockInterrupts
+        ]
     ]
 
     "Created: / 19.4.1996 / 10:54:08 / cg"
@@ -3772,11 +3769,11 @@
      This is a private helper for directed dependencies."
 
     [
-	(aCollection isNil or:[aCollection isEmpty]) ifTrue:[
-	    NonWeakDependencies removeKey:self ifAbsent:nil
-	] ifFalse:[
-	    NonWeakDependencies at:self put:aCollection
-	]
+        (aCollection isNil or:[aCollection isEmpty]) ifTrue:[
+            NonWeakDependencies removeKey:self ifAbsent:nil
+        ] ifFalse:[
+            NonWeakDependencies at:self put:aCollection
+        ]
     ] valueUninterruptably
 
     "Created: 19.4.1996 / 11:07:47 / cg"
@@ -3795,29 +3792,29 @@
 
     wasBlocked := OperatingSystem blockInterrupts.
     [
-	|deps n|
-
-	deps := self nonWeakDependents.
-	deps size ~~ 0 ifTrue:[
-	    deps class == Array ifTrue:[
-		(deps at:1) == anObject ifTrue:[
-		    self nonWeakDependents:nil
-		]
-	    ] ifFalse:[
-		deps remove:anObject ifAbsent:[].
-		(n := deps size) == 0 ifTrue:[
-		    self nonWeakDependents:nil
-		] ifFalse:[
-		    n == 1 ifTrue:[
-			self nonWeakDependents:(Array with:(deps first))
-		    ]
-		]
-	    ]
-	]
+        |deps n|
+
+        deps := self nonWeakDependents.
+        deps size ~~ 0 ifTrue:[
+            deps class == Array ifTrue:[
+                (deps at:1) == anObject ifTrue:[
+                    self nonWeakDependents:nil
+                ]
+            ] ifFalse:[
+                deps remove:anObject ifAbsent:[].
+                (n := deps size) == 0 ifTrue:[
+                    self nonWeakDependents:nil
+                ] ifFalse:[
+                    n == 1 ifTrue:[
+                        self nonWeakDependents:(Array with:(deps first))
+                    ]
+                ]
+            ]
+        ]
     ] ensure:[
-	wasBlocked ifFalse:[
-	    OperatingSystem unblockInterrupts
-	]
+        wasBlocked ifFalse:[
+            OperatingSystem unblockInterrupts
+        ]
     ]
 
     "Created: / 19.4.1996 / 11:44:44 / cg"
@@ -3850,8 +3847,8 @@
     "/ what a kludge - Dolphin and Squeak mean: printOn: a stream;
     "/ ST/X (and some old ST80's) mean: draw-yourself on a GC.
     aGCOrStream isStream ifTrue:[
-	self printOn:aGCOrStream.
-	^ self
+        self printOn:aGCOrStream.
+        ^ self
     ].
     ^ self displayOn:aGCOrStream x:0 y:0.
 
@@ -3887,9 +3884,9 @@
     s := self isString ifTrue:[self] ifFalse:[self displayString].
     yBaseline := y "+ aGc font ascent".
     opaque ifTrue:[
-	aGc displayOpaqueString:s x:x y:yBaseline.
+        aGc displayOpaqueString:s x:x y:yBaseline.
     ] ifFalse:[
-	aGc displayString:s x:x y:yBaseline.
+        aGc displayString:s x:x y:yBaseline.
     ].
 
     "Modified: 29.5.1996 / 16:29:38 / cg"
@@ -3911,14 +3908,14 @@
      but sometimes redefined for a better look.
 
      Note: the base method (used by the inspector) is #displayOn:.
-	   So you should implement #displayOn: instead of #displayString in subclasses."
+           So you should implement #displayOn: instead of #displayString in subclasses."
 
     |s|
 
     "/ attention: TextStream is not present in ultra-mini standalone apps
     s := TextStream isNil
-	    ifTrue:['' writeStream]
-	    ifFalse:[TextStream on:(String new:32)].
+            ifTrue:['' writeStream]
+            ifFalse:[TextStream on:(String new:32)].
     self displayOn:s.
     ^ s contents
 
@@ -4088,31 +4085,31 @@
     stop := aSpecArray size.
 
     2 to:stop by:2 do:[:i|
-	sel := aSpecArray at:i.
-	litVal := aSpecArray at:i + 1.
-
-	(self respondsTo:sel) ifTrue:[
-	    val := litVal decodeAsLiteralArray.
-	    self perform:sel with:val
-	] ifFalse:[
-	    "/ that's a debug halt,
-	    "/ it should probably be removed (to simply ignore unhandled attributes)...
-	    "/ for now, it is left in, in order to easily find incompatibilities between
-	    "/ VW and ST/X.
-	    self breakPoint:#cg.
-
-	    msg := '%1: unhandled literalArrayEncoding attribute:'
-			bindWith:self class name
-			with:sel.
-	    UnhandledAttributeInLiteralArrayErrorSignal isHandled ifTrue:[
-		ex := UnhandledAttributeInLiteralArrayErrorSignal new.
-		ex badLiteralArray:self.
-		ex parameter:sel.
-		ex notify:msg.
-	    ] ifFalse:[
-		msg infoPrintCR.
-	    ].
-	]
+        sel := aSpecArray at:i.
+        litVal := aSpecArray at:i + 1.
+
+        (self respondsTo:sel) ifTrue:[
+            val := litVal decodeAsLiteralArray.
+            self perform:sel with:val
+        ] ifFalse:[
+            "/ that's a debug halt,
+            "/ it should probably be removed (to simply ignore unhandled attributes)...
+            "/ for now, it is left in, in order to easily find incompatibilities between
+            "/ VW and ST/X.
+            self breakPoint:#cg.
+
+            msg := '%1: unhandled literalArrayEncoding attribute:'
+                        bindWith:self class name
+                        with:sel.
+            UnhandledAttributeInLiteralArrayErrorSignal isHandled ifTrue:[
+                ex := UnhandledAttributeInLiteralArrayErrorSignal new.
+                ex badLiteralArray:self.
+                ex parameter:sel.
+                ex notify:msg.
+            ] ifFalse:[
+                msg infoPrintCR.
+            ].
+        ]
     ]
 !
 
@@ -4125,7 +4122,7 @@
     |names encoding cls skipped slots|
 
     self isLiteral ifTrue:[
-	^ self
+        ^ self
     ].
 
     slots    := self literalArrayEncodingSlotOrder.
@@ -4136,22 +4133,22 @@
     encoding add:cls name.
 
     slots do:[:instSlot |
-	|value nm|
-
-	nm := names at:instSlot.
-	(skipped includes:nm) ifFalse:[
-	    (value := self instVarAt:instSlot) notNil ifTrue:[
-		encoding add:(nm asMutator).
-		encoding add:value literalArrayEncoding
-	    ]
-	]
+        |value nm|
+
+        nm := names at:instSlot.
+        (skipped includes:nm) ifFalse:[
+            (value := self instVarAt:instSlot) notNil ifTrue:[
+                encoding add:(nm asMutator).
+                encoding add:value literalArrayEncoding
+            ]
+        ]
     ].
     ^ encoding asArray
 
     "
-	(1 -> 2) literalArrayEncoding
-	DebugView menuSpec decodeAsLiteralArray literalArrayEncoding  =
-	   DebugView menuSpec
+        (1 -> 2) literalArrayEncoding
+        DebugView menuSpec decodeAsLiteralArray literalArrayEncoding  =
+           DebugView menuSpec
     "
 !
 
@@ -4214,8 +4211,8 @@
     <resource: #skipInDebuggersWalkBack>
 
     ^ VMInternalError
-	  raiseWith:someReceiver
-	  errorString:('bad class in send of #' , aMessage selector)
+          raiseWith:someReceiver
+          errorString:('bad class in send of #' , aMessage selector)
 
     "Modified: 23.1.1997 / 00:05:39 / cg"
 !
@@ -4352,7 +4349,7 @@
     <resource: #skipInDebuggersWalkBack>
 
     mayProceed ifTrue:[
-	^ ProceedableError raiseRequestWith:#error: errorString:aString
+        ^ ProceedableError raiseRequestWith:#error: errorString:aString
     ].
 
     Error raiseWith:#error: errorString:aString
@@ -4481,7 +4478,7 @@
     <resource: #skipInDebuggersWalkBack>
 
     index isInteger ifFalse:[
-	^ self indexNotInteger:index
+        ^ self indexNotInteger:index
     ].
     ^ self subscriptBoundsError:index
 !
@@ -4496,9 +4493,9 @@
 "/    ^ self error:'bad assign of ' , self printString ,
 "/                  ' (' , self class name , ') to integer-typed variable'
     ^ InvalidTypeError
-	raiseRequestErrorString:(
-	    'bad assign of ' , self printString ,
-		  ' (' , self class name , ') to integer-typed variable')
+        raiseRequestErrorString:(
+            'bad assign of ' , self printString ,
+                  ' (' , self class name , ') to integer-typed variable')
 
     "Modified: / 02-11-2012 / 10:25:36 / cg"
 !
@@ -4512,7 +4509,7 @@
 
     "/ self error:'not an executable code object'
     ^ ExecutionError
-	raiseRequestErrorString:'not an executable code object'
+        raiseRequestErrorString:'not an executable code object'
 
     "Created: / 01-08-1997 / 00:16:44 / cg"
 !
@@ -4538,7 +4535,7 @@
 
     "/ ^ self error:'argument must be a Rectangle'
     ^ InvalidTypeError
-	raiseRequestErrorString:'argument must be a Rectangle'
+        raiseRequestErrorString:'argument must be a Rectangle'
 
     "Modified: / 02-11-2012 / 10:24:53 / cg"
 !
@@ -4552,7 +4549,7 @@
 
     "/ ^ self error:'argument must be a String'
     ^ InvalidTypeError
-	raiseRequestErrorString:'argument must be a String'
+        raiseRequestErrorString:'argument must be a String'
 
     "Modified: / 02-11-2012 / 10:24:35 / cg"
 !
@@ -4567,7 +4564,7 @@
     <resource: #skipInDebuggersWalkBack>
 
     ^ SubscriptOutOfBoundsError
-	raiseRequestErrorString:'receiver has no indexed variables'
+        raiseRequestErrorString:'receiver has no indexed variables'
 
     "
      1234 at:4
@@ -4589,7 +4586,7 @@
     sender := thisContext sender.
 
     ^ UnimplementedFunctionalityError
-	raiseRequestWith:(Message selector:sender selector arguments:sender args)
+        raiseRequestWith:(Message selector:sender selector arguments:sender args)
 
     "Modified: / 02-11-2012 / 10:24:12 / cg"
 !
@@ -4608,20 +4605,20 @@
     "do loop to take care of super sends"
     sender := thisContext sender.
     [
-	selector := sender selector.
-	selector == #primitiveFailed: or:[selector == #primitiveFailed]
+        selector := sender selector.
+        selector == #primitiveFailed: or:[selector == #primitiveFailed]
     ] whileTrue:[sender := sender sender].
 
     ^ PrimitiveFailure raiseRequestWith:(Message selector:selector arguments:sender args)
-		       in:sender.
+                       in:sender.
 
     "
      1234 primitiveFailed
 
      [
-	ExternalBytes new   basicAt:40
+        ExternalBytes new   basicAt:40
      ] on:PrimitiveFailure do:[:ex|
-	ex inspect
+        ex inspect
      ]
     "
 !
@@ -4639,13 +4636,13 @@
     "do loop to take care of super sends"
     sender := thisContext sender.
     [
-	selector := sender selector.
-	selector == #primitiveFailed: or:[selector == #primitiveFailed]
+        selector := sender selector.
+        selector == #primitiveFailed: or:[selector == #primitiveFailed]
     ] whileTrue:[sender := sender sender].
 
     ^ PrimitiveFailure raiseRequestWith:(Message selector:selector arguments:sender args)
-		       errorString:messageString
-		       in:sender.
+                       errorString:messageString
+                       in:sender.
 
     "
      1234 primitiveFailed:'this is a test'
@@ -4666,7 +4663,7 @@
     sender := thisContext sender.
 
     ^ UnimplementedFunctionalityError
-	raiseRequestWith:(Message selector:sender selector arguments:sender args)
+        raiseRequestWith:(Message selector:sender selector arguments:sender args)
 
      "
       self shouldImplement
@@ -4687,8 +4684,8 @@
     sender := thisContext sender.
 
     ^ UnimplementedFunctionalityError
-	raiseRequestWith:(Message selector:sender selector arguments:sender args)
-	errorString:what
+        raiseRequestWith:(Message selector:sender selector arguments:sender args)
+        errorString:what
 
      "
       self shouldImplement:'foobar'
@@ -4701,7 +4698,7 @@
     <resource: #skipInDebuggersWalkBack>
 
     ^ ExecutionError
-	raiseRequestErrorString:'Oops, this may never reached. Something somewhere was terribly wrong.'.
+        raiseRequestErrorString:'Oops, this may never reached. Something somewhere was terribly wrong.'.
 
     "Modified: / 20-04-2005 / 18:59:28 / janfrog"
 !
@@ -4727,7 +4724,7 @@
     <resource: #skipInDebuggersWalkBack>
 
     ^ MethodNotAppropriateError
-	raiseRequestErrorString:'method/functionality is not appropriate for class'.
+        raiseRequestErrorString:'method/functionality is not appropriate for class'.
 
     "Modified: / 02-11-2012 / 10:02:25 / cg"
 !
@@ -4777,8 +4774,8 @@
     <resource: #skipInDebuggersWalkBack>
 
     ^ SubscriptOutOfBoundsError
-	raiseRequestWith:anIndex
-	errorString:('subscript (' , anIndex printString , ') out of bounds')
+        raiseRequestWith:anIndex
+        errorString:('subscript (' , anIndex printString , ') out of bounds')
 
     "Modified: / 17.11.2001 / 22:49:56 / cg"
 !
@@ -4795,9 +4792,9 @@
 "/                  ' (' , self class name , ') to typed variable'
 
     ^ InvalidTypeError
-	raiseRequestErrorString:
-	    ('bad assign of ' , self printString ,
-		  ' (' , self class name , ') to typed variable')
+        raiseRequestErrorString:
+            ('bad assign of ' , self printString ,
+                  ' (' , self class name , ') to typed variable')
 
     "Modified: / 02-11-2012 / 10:19:15 / cg"
 ! !
@@ -4808,12 +4805,12 @@
     "add a debugger hook. Any registered hook is evaluated with the exception as
      argument before a real debugger is entered.
      Hooks can be used for two purposes:
-	- record exception information in a log file
-	- filter exceptions and either decide to ignore them or to open an alternative
-	  debugger (depending on the exception type, maybe)"
+        - record exception information in a log file
+        - filter exceptions and either decide to ignore them or to open an alternative
+          debugger (depending on the exception type, maybe)"
 
     DebuggerHooks isNil ifTrue:[
-	DebuggerHooks := OrderedCollection new.
+        DebuggerHooks := OrderedCollection new.
     ].
     DebuggerHooks add:aBlock
 
@@ -4834,11 +4831,11 @@
     "
     "
      Object addDebuggerHook:[:ex | '/tmp/stx.log' asFilename
-				   appendingFileDo:[:s |
-					s nextPutLine:'----------------------'.
-					(Timestamp now printOn:s). s cr.
-					ex suspendedContext fullPrintAllOn:s
-				   ]].
+                                   appendingFileDo:[:s |
+                                        s nextPutLine:'----------------------'.
+                                        (Timestamp now printOn:s). s cr.
+                                        ex suspendedContext fullPrintAllOn:s
+                                   ]].
      (1 / (1-1)).
      Object removeDebuggerHook:(DebuggerHooks first).
     "
@@ -4858,34 +4855,34 @@
     (Processor isNil
     or:[Processor activeProcessIsSystemProcess
     or:[Smalltalk isInitialized not]]) ifTrue:[
-	^ MiniDebugger
+        ^ MiniDebugger
     ].
     (Screen isNil or:[Screen default isNil or:[Screen default isOpen not]]) ifTrue:[
-	Debugger isNil ifTrue:[^ nil].
-	^ MiniDebugger
+        Debugger isNil ifTrue:[^ nil].
+        ^ MiniDebugger
     ].
 
     context := thisContext.
     context := context findNextContextWithSelector:aSelector or:nil or:nil.
     [context notNil] whileTrue:[
-	((context receiver class == Debugger)
-	 and:[context selector == aSelector]) ifTrue:[
-	    "we are already in some Debugger"
-	    (Debugger == MiniDebugger) ifTrue:[
-		"we are already in the MiniDebugger"
-		ErrorRecursion ifFalse:[
-		    Smalltalk fatalAbort:'recursive error ...'
-		]
-	    ].
-	    MiniDebugger isNil ifTrue:[
-		Smalltalk fatalAbort:'no debugger'
-	    ].
-
-	    "ok, an error occurred while in the graphical debugger;
-	     lets try MiniDebugger"
-	    ^ MiniDebugger
-	].
-	context := context findNextContextWithSelector:aSelector or:nil or:nil.
+        ((context receiver class == Debugger)
+         and:[context selector == aSelector]) ifTrue:[
+            "we are already in some Debugger"
+            (Debugger == MiniDebugger) ifTrue:[
+                "we are already in the MiniDebugger"
+                ErrorRecursion ifFalse:[
+                    Smalltalk fatalAbort:'recursive error ...'
+                ]
+            ].
+            MiniDebugger isNil ifTrue:[
+                Smalltalk fatalAbort:'no debugger'
+            ].
+
+            "ok, an error occurred while in the graphical debugger;
+             lets try MiniDebugger"
+            ^ MiniDebugger
+        ].
+        context := context findNextContextWithSelector:aSelector or:nil or:nil.
     ].
     "not within Debugger - no problem"
     ^ Debugger
@@ -4909,47 +4906,47 @@
      ignore will raise an AbortOperationRequest.
     "
     Debugger isNil ifTrue:[
-	msgString := 'Error: ' , msgString.
-
-	thisContext isRecursive ifTrue:[
-	    msgString errorPrintCR.
-	    Smalltalk fatalAbort:'recursive unhandled exception'
-	].
-
-	Smalltalk isStandAloneApp ifTrue:[
-	    (ex creator == NoHandlerError) ifTrue:[
-		(HaltInterrupt handles:ex exception) ifTrue:[
-		    "/ 'Halt ignored' infoPrintCR.
-		    ^ nil
-		].
-		"don't output the message, if the exception is a UserInterrupt (CTRL-C)"
-		(ex exception creator == UserInterrupt) ifTrue:[
-		    ex description errorPrintCR.
-		    OperatingSystem exit:130.
-		].
-	    ].
-	].
-
-	(Dialog notNil and:[Screen default notNil]) ifTrue:[
-	    self
-		errorNotify:msgString
-		from:ex suspendedContext
-		allowDebug:false
-		mayProceed:ex willProceed.
-
-	    "/ arrive here if proceeded...
-	    ^ nil
-	].
-
-	"don't output the message, if the exception is a UserInterrupt (CTRL-C)"
-	(ex creator == NoHandlerError
-	 and:[ex exception creator == UserInterrupt]) ifTrue:[
-	    OperatingSystem exit:130.
-	].
-	msgString errorPrintCR.
-	'Backtrace:' errorPrintCR.
-	thisContext fullPrintAll.
-	OperatingSystem exit:1
+        msgString := 'Error: ' , msgString.
+
+        thisContext isRecursive ifTrue:[
+            msgString errorPrintCR.
+            Smalltalk fatalAbort:'recursive unhandled exception'
+        ].
+
+        Smalltalk isStandAloneApp ifTrue:[
+            (ex creator == NoHandlerError) ifTrue:[
+                (HaltInterrupt handles:ex exception) ifTrue:[
+                    "/ 'Halt ignored' infoPrintCR.
+                    ^ nil
+                ].
+                "don't output the message, if the exception is a UserInterrupt (CTRL-C)"
+                (ex exception creator == UserInterrupt) ifTrue:[
+                    ex description errorPrintCR.
+                    OperatingSystem exit:130.
+                ].
+            ].
+        ].
+
+        (Dialog notNil and:[Screen default notNil]) ifTrue:[
+            self
+                errorNotify:msgString
+                from:ex suspendedContext
+                allowDebug:false
+                mayProceed:ex willProceed.
+
+            "/ arrive here if proceeded...
+            ^ nil
+        ].
+
+        "don't output the message, if the exception is a UserInterrupt (CTRL-C)"
+        (ex creator == NoHandlerError
+         and:[ex exception creator == UserInterrupt]) ifTrue:[
+            OperatingSystem exit:130.
+        ].
+        msgString errorPrintCR.
+        'Backtrace:' errorPrintCR.
+        thisContext fullPrintAll.
+        OperatingSystem exit:1
     ].
 
     "
@@ -4957,7 +4954,7 @@
     "
     debugger := self appropriateDebugger:(thisContext selector).
     debugger isNil ifTrue:[
-	^ AbortOperationRequest raiseRequest
+        ^ AbortOperationRequest raiseRequest
     ].
 
     "/ call any registered debug hooks.
@@ -4965,9 +4962,9 @@
     "/ ex-message (ex proceed, ex return etc.) or raise an Abort signal.
     "/ However, the real intent for hooks is to allow saving exceptions in a log file...
     DebuggerHooks notNil ifTrue:[
-	DebuggerHooks do:[:eachHook |
-	    eachHook value:ex.
-	].
+        DebuggerHooks do:[:eachHook |
+            eachHook value:ex.
+        ].
     ].
     ^ debugger enterException:ex.
 
@@ -4978,8 +4975,8 @@
     "remove a debugger hook."
 
     DebuggerHooks notNil ifTrue:[
-	DebuggerHooks removeIdentical:aBlock.
-	DebuggerHooks isNil ifTrue:[ DebuggerHooks := nil ].
+        DebuggerHooks removeIdentical:aBlock.
+        DebuggerHooks isNil ifTrue:[ DebuggerHooks := nil ].
     ].
 ! !
 
@@ -5001,7 +4998,7 @@
     ^ 0
 
     "
-	[1 // 0] on:ArithmeticError do:9999
+        [1 // 0] on:ArithmeticError do:9999
     "
 !
 
@@ -5015,18 +5012,18 @@
      style ... (the idea was borrowed from the Self language).
 
      WARNING: dont 'optimize' away ifXXX: blocks
-	      (i.e. do NOT replace
-			foo ifTrue:[var1] ifFalse:[var2]
-	       by:
-			foo ifTrue:var1 ifFalse:var2
-	      )
-	      - the compilers will only generate inline code for the if,
-		iff the argument(s) are blocks - otherwise, a true send is
-		generated.
-	      This 'optimization' will work semantically correct,
-	      but execute SLOWER instead.
-
-	      Using constants (foo ifTrue:1 ifFalse:2) does not introduce a performance penalty."
+              (i.e. do NOT replace
+                        foo ifTrue:[var1] ifFalse:[var2]
+               by:
+                        foo ifTrue:var1 ifFalse:var2
+              )
+              - the compilers will only generate inline code for the if,
+                iff the argument(s) are blocks - otherwise, a true send is
+                generated.
+              This 'optimization' will work semantically correct,
+              but execute SLOWER instead.
+
+              Using constants (foo ifTrue:1 ifFalse:2) does not introduce a performance penalty."
 
     ^ self
 
@@ -5055,8 +5052,8 @@
      ^ self
 
     "
-	[ 'abc' ] valueWithPossibleArguments:#(1 2 3)
-	'abc' valueWithPossibleArguments:#(1 2 3)
+        [ 'abc' ] valueWithPossibleArguments:#(1 2 3)
+        'abc' valueWithPossibleArguments:#(1 2 3)
     "
 ! !
 
@@ -5184,30 +5181,30 @@
      used from other C subsystems too, to upcast errors.
      Especially, for subsystems which call errorHandler functions asynchronously.
      IDs (currently) used:
-	#DisplayError ..... x-error interrupt
-	#XtError      ..... xt-error interrupt (Xt interface is not yet published)
+        #DisplayError ..... x-error interrupt
+        #XtError      ..... xt-error interrupt (Xt interface is not yet published)
     "
 
     |handlers handler|
 
     handlers := ObjectMemory registeredErrorInterruptHandlers.
     handlers notNil ifTrue:[
-	handler := handlers at:errorID ifAbsent:nil.
-	handler notNil ifTrue:[
-	    "/
-	    "/ handler found; let it do whatever it wants ...
-	    "/
-	    handler errorInterrupt:errorID with:aParameter.
-	    ^ self
-	].
+        handler := handlers at:errorID ifAbsent:nil.
+        handler notNil ifTrue:[
+            "/
+            "/ handler found; let it do whatever it wants ...
+            "/
+            handler errorInterrupt:errorID with:aParameter.
+            ^ self
+        ].
     ].
 
     "/
     "/ no handler - raise errorSignal passing the errorId as parameter
     "/
     ^ Error
-	raiseRequestWith:errorID
-	errorString:('Subsystem error. ErrorID = ' , errorID printString)
+        raiseRequestWith:errorID
+        errorString:('Subsystem error. ErrorID = ' , errorID printString)
 !
 
 exceptionInterrupt
@@ -5233,12 +5230,12 @@
     where := thisContext sender.
     rec := where receiver.
     rec isNumber ifTrue:[
-	^ rec class
-	    raise:#domainErrorSignal
-	    receiver:rec
-	    selector:where selector
-	    arguments:(where args asArray)
-	    errorString:'floating point exception'
+        ^ rec class
+            raise:#domainErrorSignal
+            receiver:rec
+            selector:where selector
+            arguments:(where args asArray)
+            errorString:'floating point exception'
     ].
 
     "/ could be in some C-library ...
@@ -5551,10 +5548,10 @@
      Start a mini debugger or exit if none is present"
 
     MiniDebugger isNil ifTrue:[
-	"a system without debugging facilities (i.e. a standalone system)
-	 output a message and exit."
-	('Object [error]: exit due to ', text, ' - and no debugger.') errorPrintCR.
-	OperatingSystem exit:99.
+        "a system without debugging facilities (i.e. a standalone system)
+         output a message and exit."
+        ('Object [error]: exit due to ', text, ' - and no debugger.') errorPrintCR.
+        OperatingSystem exit:99.
     ].
     MiniDebugger enterWithMessage:text mayProceed:true.
 !
@@ -5613,7 +5610,7 @@
     int hash0;
 
     if (InterruptPending == nil) {
-	struct inlineCache *pIlc;
+        struct inlineCache *pIlc;
 
 # define nways 2
 # define nilcs 131
@@ -5631,7 +5628,7 @@
 
 # define SEL_AND_ILC_INIT_131(l) SEL_AND_ILC_INIT_128(l) , SEL_AND_ILC_INIT_2(l) , SEL_AND_ILC_INIT_1(l)
 
-	static struct { OBJ sel[nways]; struct inlineCache ilc[nways]; int flip; } sel_and_ilc[nilcs] = { SEL_AND_ILC_INIT_131(@line) };
+        static struct { OBJ sel[nways]; struct inlineCache ilc[nways]; int flip; } sel_and_ilc[nilcs] = { SEL_AND_ILC_INIT_131(@line) };
 
 # undef SEL_AND_ILC_INIT_1
 # undef SEL_AND_ILC_INIT_2
@@ -5647,37 +5644,37 @@
 # undef SEL_AND_ILC_INIT_257
 
 # define TRY(n)                                  \
-	if (sel == sel_and_ilc[hash0].sel[n]) { \
-	    pIlc = &sel_and_ilc[hash0].ilc[n];  \
-	    goto perform0_send_and_return;      \
-	}
-
-	if (__isNonNilObject(sel)) {
-	    hash0 = __MAKE_HASH__(__GET_HASH(sel)) % nilcs;
-	} else {
-	    /* sel is either nil or smallint, use its value as hash */
-	    hash0 = (INT)sel % nilcs;
-	}
-
-	TRY(0);
-	TRY(1);
+        if (sel == sel_and_ilc[hash0].sel[n]) { \
+            pIlc = &sel_and_ilc[hash0].ilc[n];  \
+            goto perform0_send_and_return;      \
+        }
+
+        if (__isNonNilObject(sel)) {
+            hash0 = __MAKE_HASH__(__GET_HASH(sel)) % nilcs;
+        } else {
+            /* sel is either nil or smallint, use its value as hash */
+            hash0 = (INT)sel % nilcs;
+        }
+
+        TRY(0);
+        TRY(1);
 
 # undef TRY
-	/*printf("Object >> #perform: #%s --> no PIC found\n", __symbolVal(aSelector));*/
-
-	pIlc = &sel_and_ilc[hash0].ilc[sel_and_ilc[hash0].flip];
-	sel_and_ilc[hash0].sel[sel_and_ilc[hash0].flip] = sel;
-	sel_and_ilc[hash0].flip = (sel_and_ilc[hash0].flip + 1) % nways;
-	pIlc->ilc_func = __SEND0ADDR__;
-	if (pIlc->ilc_poly) {
-	    __flushPolyCache(pIlc->ilc_poly);
-	    pIlc->ilc_poly = 0;
-	}
+        /*printf("Object >> #perform: #%s --> no PIC found\n", __symbolVal(aSelector));*/
+
+        pIlc = &sel_and_ilc[hash0].ilc[sel_and_ilc[hash0].flip];
+        sel_and_ilc[hash0].sel[sel_and_ilc[hash0].flip] = sel;
+        sel_and_ilc[hash0].flip = (sel_and_ilc[hash0].flip + 1) % nways;
+        pIlc->ilc_func = __SEND0ADDR__;
+        if (pIlc->ilc_poly) {
+            __flushPolyCache(pIlc->ilc_poly);
+            pIlc->ilc_poly = 0;
+        }
 perform0_send_and_return:
-	RETURN ( (*(pIlc->ilc_func))(self, sel, nil, pIlc) );
+        RETURN ( (*(pIlc->ilc_func))(self, sel, nil, pIlc) );
     } else {
-	static struct inlineCache ilc0 = __DUMMYILCSELF0(@line+1);
-	RETURN (_SEND0(self, aSelector, nil, &ilc0));
+        static struct inlineCache ilc0 = __DUMMYILCSELF0(@line+1);
+        RETURN (_SEND0(self, aSelector, nil, &ilc0));
     }
 #endif /* not __SCHTEAM__ */
 %}.
@@ -5691,7 +5688,7 @@
      to execute a method in ANY superclass of the receiver (not just the
      immediate superclass).
      Thus, it is (theoretically) possible to do
-	 '5 perform:#< inClass:Magnitude withArguments:#(6)'
+         '5 perform:#< inClass:Magnitude withArguments:#(6)'
      and evaluate Magnitudes compare method even if there was one in Number.
      This method is used by the interpreter to evaluate super sends
      and could be used for very special behavior (language extension ?).
@@ -5705,8 +5702,8 @@
     "
     myClass := self class.
     (myClass == aClass or:[myClass isSubclassOf:aClass]) ifFalse:[
-	self error:'lookup-class argument is not a superclass of the receiver'.
-	^ nil
+        self error:'lookup-class argument is not a superclass of the receiver'.
+        ^ nil
     ].
 %{
 #ifdef __SCHTEAM__
@@ -5715,166 +5712,166 @@
     int nargs, i;
 
     if (__isArrayLike(argArray)) {
-	nargs = __arraySize(argArray);
-	argP = __arrayVal(argArray);
+        nargs = __arraySize(argArray);
+        argP = __arrayVal(argArray);
     } else {
-	if (__isNonNilObject(argArray)) {
-	    static struct inlineCache ilcSize = __ILC0(@line+1);
-	    numberOfArgs = (*ilcSize.ilc_func)(argArray, @symbol(size), nil, &ilcSize);
-	    if (!__isSmallInteger(numberOfArgs))
-		goto bad;
-	    nargs = __intVal(numberOfArgs);
-	    argP = (OBJ *)(&a1);
-	    for (i=1; i <= nargs; i++) {
-		*argP++ = __AT_(argArray, __mkSmallInteger(i));
-	    }
-	    argP = (OBJ *)(&a1);
-	} else {
-	    nargs = 0;
-	}
+        if (__isNonNilObject(argArray)) {
+            static struct inlineCache ilcSize = __ILC0(@line+1);
+            numberOfArgs = (*ilcSize.ilc_func)(argArray, @symbol(size), nil, &ilcSize);
+            if (!__isSmallInteger(numberOfArgs))
+                goto bad;
+            nargs = __intVal(numberOfArgs);
+            argP = (OBJ *)(&a1);
+            for (i=1; i <= nargs; i++) {
+                *argP++ = __AT_(argArray, __mkSmallInteger(i));
+            }
+            argP = (OBJ *)(&a1);
+        } else {
+            nargs = 0;
+        }
     }
     switch (nargs) {
-	case 0:
-	    {
-		static struct inlineCache ilc0 = __DUMMYILCSELF0(@line+1);
-		RETURN ( _SEND0(self, aSelector, aClass, &ilc0));
-	    }
-
-	case 1:
-	    {
-		static struct inlineCache ilc1 = __DUMMYILCSELF1(@line+1);
-		RETURN ( _SEND1(self, aSelector, aClass, &ilc1, argP[0]));
-	    }
-
-	case 2:
-	    {
-		static struct inlineCache ilc2 = __DUMMYILCSELF2(@line+1);
-		RETURN ( _SEND2(self, aSelector, aClass, &ilc2, argP[0], argP[1]));
-	    }
-
-	case 3:
-	    {
-		static struct inlineCache ilc3 = __DUMMYILCSELF3(@line+1);
-		RETURN ( _SEND3(self, aSelector, aClass, &ilc3,
-				argP[0], argP[1], argP[2]));
-	    }
-
-	case 4:
-	    {
-		static struct inlineCache ilc4 = __DUMMYILCSELF4(@line+1);
-		RETURN ( _SEND4(self, aSelector, aClass, &ilc4,
-				argP[0], argP[1], argP[2], argP[3]));
-	    }
-
-	case 5:
-	    {
-		static struct inlineCache ilc5 = __DUMMYILCSELF5(@line+1);
-		RETURN ( _SEND5(self, aSelector, aClass, &ilc5,
-				argP[0], argP[1], argP[2], argP[3], argP[4]));
-	    }
-
-	case 6:
-	    {
-		static struct inlineCache ilc6 = __DUMMYILCSELF6(@line+1);
-		RETURN ( _SEND6(self, aSelector, aClass, &ilc6,
-				argP[0], argP[1], argP[2], argP[3], argP[4], argP[5]));
-	    }
-
-	case 7:
-	    {
-		static struct inlineCache ilc7 = __DUMMYILCSELF7(@line+1);
-		RETURN ( _SEND7(self, aSelector, aClass, &ilc7,
-				argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
-				argP[6]));
-	    }
-
-	case 8:
-	    {
-		static struct inlineCache ilc8 = __DUMMYILCSELF8(@line+1);
-		RETURN ( _SEND8(self, aSelector, aClass, &ilc8,
-				argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
-				argP[6], argP[7]));
-	    }
-
-	case 9:
-	    {
-		static struct inlineCache ilc9 = __DUMMYILCSELF9(@line+1);
-		RETURN ( _SEND9(self, aSelector, aClass, &ilc9,
-				argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
-				argP[6], argP[7], argP[8]));
-	    }
-
-	case 10:
-	    {
-		static struct inlineCache ilc10 = __DUMMYILCSELF10(@line+1);
-		RETURN ( _SEND10(self, aSelector, aClass, &ilc10,
-				 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
-				 argP[6], argP[7], argP[8], argP[9]));
-	    }
-
-	case 11:
-	    {
-		static struct inlineCache ilc11 = __DUMMYILCSELF11(@line+1);
-		RETURN ( _SEND11(self, aSelector, aClass, &ilc11,
-				 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
-				 argP[6], argP[7], argP[8], argP[9], argP[10]));
-	    }
-
-	case 12:
-	    {
-		static struct inlineCache ilc12 = __DUMMYILCSELF12(@line+1);
-		RETURN ( _SEND12(self, aSelector, aClass, &ilc12,
-				 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
-				 argP[6], argP[7], argP[8], argP[9], argP[10],
-				 argP[11]));
-	    }
-
-	case 13:
-	    {
-		static struct inlineCache ilc13 = __DUMMYILCSELF13(@line+1);
-		RETURN ( _SEND13(self, aSelector, aClass, &ilc13,
-				 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
-				 argP[6], argP[7], argP[8], argP[9], argP[10],
-				 argP[11], argP[12]));
-	    }
-
-	case 14:
-	    {
-		static struct inlineCache ilc14 = __DUMMYILCSELF14(@line+1);
-		RETURN ( _SEND14(self, aSelector, aClass, &ilc14,
-				 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
-				 argP[6], argP[7], argP[8], argP[9], argP[10],
-				 argP[11], argP[12], argP[13]));
-	    }
-
-	case 15:
-	    {
-		static struct inlineCache ilc15 = __DUMMYILCSELF15(@line+1);
-		RETURN ( _SEND15(self, aSelector, aClass, &ilc15,
-				 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
-				 argP[6], argP[7], argP[8], argP[9], argP[10],
-				 argP[11], argP[12], argP[13], argP[14]));
-	    }
+        case 0:
+            {
+                static struct inlineCache ilc0 = __DUMMYILCSELF0(@line+1);
+                RETURN ( _SEND0(self, aSelector, aClass, &ilc0));
+            }
+
+        case 1:
+            {
+                static struct inlineCache ilc1 = __DUMMYILCSELF1(@line+1);
+                RETURN ( _SEND1(self, aSelector, aClass, &ilc1, argP[0]));
+            }
+
+        case 2:
+            {
+                static struct inlineCache ilc2 = __DUMMYILCSELF2(@line+1);
+                RETURN ( _SEND2(self, aSelector, aClass, &ilc2, argP[0], argP[1]));
+            }
+
+        case 3:
+            {
+                static struct inlineCache ilc3 = __DUMMYILCSELF3(@line+1);
+                RETURN ( _SEND3(self, aSelector, aClass, &ilc3,
+                                argP[0], argP[1], argP[2]));
+            }
+
+        case 4:
+            {
+                static struct inlineCache ilc4 = __DUMMYILCSELF4(@line+1);
+                RETURN ( _SEND4(self, aSelector, aClass, &ilc4,
+                                argP[0], argP[1], argP[2], argP[3]));
+            }
+
+        case 5:
+            {
+                static struct inlineCache ilc5 = __DUMMYILCSELF5(@line+1);
+                RETURN ( _SEND5(self, aSelector, aClass, &ilc5,
+                                argP[0], argP[1], argP[2], argP[3], argP[4]));
+            }
+
+        case 6:
+            {
+                static struct inlineCache ilc6 = __DUMMYILCSELF6(@line+1);
+                RETURN ( _SEND6(self, aSelector, aClass, &ilc6,
+                                argP[0], argP[1], argP[2], argP[3], argP[4], argP[5]));
+            }
+
+        case 7:
+            {
+                static struct inlineCache ilc7 = __DUMMYILCSELF7(@line+1);
+                RETURN ( _SEND7(self, aSelector, aClass, &ilc7,
+                                argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
+                                argP[6]));
+            }
+
+        case 8:
+            {
+                static struct inlineCache ilc8 = __DUMMYILCSELF8(@line+1);
+                RETURN ( _SEND8(self, aSelector, aClass, &ilc8,
+                                argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
+                                argP[6], argP[7]));
+            }
+
+        case 9:
+            {
+                static struct inlineCache ilc9 = __DUMMYILCSELF9(@line+1);
+                RETURN ( _SEND9(self, aSelector, aClass, &ilc9,
+                                argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
+                                argP[6], argP[7], argP[8]));
+            }
+
+        case 10:
+            {
+                static struct inlineCache ilc10 = __DUMMYILCSELF10(@line+1);
+                RETURN ( _SEND10(self, aSelector, aClass, &ilc10,
+                                 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
+                                 argP[6], argP[7], argP[8], argP[9]));
+            }
+
+        case 11:
+            {
+                static struct inlineCache ilc11 = __DUMMYILCSELF11(@line+1);
+                RETURN ( _SEND11(self, aSelector, aClass, &ilc11,
+                                 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
+                                 argP[6], argP[7], argP[8], argP[9], argP[10]));
+            }
+
+        case 12:
+            {
+                static struct inlineCache ilc12 = __DUMMYILCSELF12(@line+1);
+                RETURN ( _SEND12(self, aSelector, aClass, &ilc12,
+                                 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
+                                 argP[6], argP[7], argP[8], argP[9], argP[10],
+                                 argP[11]));
+            }
+
+        case 13:
+            {
+                static struct inlineCache ilc13 = __DUMMYILCSELF13(@line+1);
+                RETURN ( _SEND13(self, aSelector, aClass, &ilc13,
+                                 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
+                                 argP[6], argP[7], argP[8], argP[9], argP[10],
+                                 argP[11], argP[12]));
+            }
+
+        case 14:
+            {
+                static struct inlineCache ilc14 = __DUMMYILCSELF14(@line+1);
+                RETURN ( _SEND14(self, aSelector, aClass, &ilc14,
+                                 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
+                                 argP[6], argP[7], argP[8], argP[9], argP[10],
+                                 argP[11], argP[12], argP[13]));
+            }
+
+        case 15:
+            {
+                static struct inlineCache ilc15 = __DUMMYILCSELF15(@line+1);
+                RETURN ( _SEND15(self, aSelector, aClass, &ilc15,
+                                 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
+                                 argP[6], argP[7], argP[8], argP[9], argP[10],
+                                 argP[11], argP[12], argP[13], argP[14]));
+            }
 
 # ifdef _SEND16
-	case 16:
-	    {
-		static struct inlineCache ilc16 = __DUMMYILCSELF16(@line+1);
-		RETURN ( _SEND16(self, aSelector, aClass, &ilc15,
-				 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
-				 argP[6], argP[7], argP[8], argP[9], argP[10],
-				 argP[11], argP[12], argP[13], argP[14], argP[15]));
-	    }
+        case 16:
+            {
+                static struct inlineCache ilc16 = __DUMMYILCSELF16(@line+1);
+                RETURN ( _SEND16(self, aSelector, aClass, &ilc15,
+                                 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
+                                 argP[6], argP[7], argP[8], argP[9], argP[10],
+                                 argP[11], argP[12], argP[13], argP[14], argP[15]));
+            }
 # endif
 # ifdef _SEND17
-	case 17:
-	    {
-		static struct inlineCache ilc17 = __DUMMYILCSELF17(@line+1);
-		RETURN ( _SEND17(self, aSelector, aClass, &ilc15,
-				 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
-				 argP[6], argP[7], argP[8], argP[9], argP[10],
-				 argP[11], argP[12], argP[13], argP[14], argP[15], argP[16]));
-	    }
+        case 17:
+            {
+                static struct inlineCache ilc17 = __DUMMYILCSELF17(@line+1);
+                RETURN ( _SEND17(self, aSelector, aClass, &ilc15,
+                                 argP[0], argP[1], argP[2], argP[3], argP[4], argP[5],
+                                 argP[6], argP[7], argP[8], argP[9], argP[10],
+                                 argP[11], argP[12], argP[13], argP[14], argP[15], argP[16]));
+            }
 # endif
 
 
@@ -5899,7 +5896,7 @@
     int hash0;
 
     if (InterruptPending == nil) {
-	struct inlineCache *pIlc;
+        struct inlineCache *pIlc;
 # undef nways
 # define nways 2
 # undef nilcs
@@ -5918,7 +5915,7 @@
 
 # define SEL_AND_ILC_INIT_131(l) SEL_AND_ILC_INIT_128(l) , SEL_AND_ILC_INIT_2(l) , SEL_AND_ILC_INIT_1(l)
 
-	static struct { OBJ sel[nways]; struct inlineCache ilc[nways]; int flip; } sel_and_ilc[nilcs] = { SEL_AND_ILC_INIT_131(@line) };
+        static struct { OBJ sel[nways]; struct inlineCache ilc[nways]; int flip; } sel_and_ilc[nilcs] = { SEL_AND_ILC_INIT_131(@line) };
 
 # undef SEL_AND_ILC_INIT_1
 # undef SEL_AND_ILC_INIT_2
@@ -5934,38 +5931,38 @@
 # undef SEL_AND_ILC_INIT_257
 
 # define TRY(n)                                  \
-	if (sel == sel_and_ilc[hash0].sel[n]) { \
-	    pIlc = &sel_and_ilc[hash0].ilc[n];  \
-	    goto perform1_send_and_return;      \
-	}
-
-	if (__isNonNilObject(sel)) {
-	    hash0 = __MAKE_HASH__(__GET_HASH(sel)) % nilcs;
-	} else {
-	    /* sel is either nil or smallint, use its value as hash */
-	    hash0 = (INT)sel % nilcs;
-	}
-
-	TRY(0);
-	TRY(1);
+        if (sel == sel_and_ilc[hash0].sel[n]) { \
+            pIlc = &sel_and_ilc[hash0].ilc[n];  \
+            goto perform1_send_and_return;      \
+        }
+
+        if (__isNonNilObject(sel)) {
+            hash0 = __MAKE_HASH__(__GET_HASH(sel)) % nilcs;
+        } else {
+            /* sel is either nil or smallint, use its value as hash */
+            hash0 = (INT)sel % nilcs;
+        }
+
+        TRY(0);
+        TRY(1);
 
 # undef TRY
-	/*printf("Object >> #perform: #%s --> no PIC found\n", __symbolVal(aSelector));*/
-
-	pIlc = &sel_and_ilc[hash0].ilc[sel_and_ilc[hash0].flip];
-	sel_and_ilc[hash0].sel[sel_and_ilc[hash0].flip] = sel;
-	sel_and_ilc[hash0].flip = (sel_and_ilc[hash0].flip + 1) % nways;
-	pIlc->ilc_func = __SEND1ADDR__;
-	if (pIlc->ilc_poly) {
-	    __flushPolyCache(pIlc->ilc_poly);
-	    pIlc->ilc_poly = 0;
-	}
+        /*printf("Object >> #perform: #%s --> no PIC found\n", __symbolVal(aSelector));*/
+
+        pIlc = &sel_and_ilc[hash0].ilc[sel_and_ilc[hash0].flip];
+        sel_and_ilc[hash0].sel[sel_and_ilc[hash0].flip] = sel;
+        sel_and_ilc[hash0].flip = (sel_and_ilc[hash0].flip + 1) % nways;
+        pIlc->ilc_func = __SEND1ADDR__;
+        if (pIlc->ilc_poly) {
+            __flushPolyCache(pIlc->ilc_poly);
+            pIlc->ilc_poly = 0;
+        }
 
 perform1_send_and_return:
-	RETURN ( (*(pIlc->ilc_func))(self, sel, nil, pIlc, arg) );
+        RETURN ( (*(pIlc->ilc_func))(self, sel, nil, pIlc, arg) );
     } else {
-	static struct inlineCache ilc1 = __DUMMYILCSELF1(@line+1);
-	RETURN (_SEND1(self, aSelector, nil, &ilc1, arg));
+        static struct inlineCache ilc1 = __DUMMYILCSELF1(@line+1);
+        RETURN (_SEND1(self, aSelector, nil, &ilc1, arg));
     }
 #endif /* not __SCHTEAM__ */
 %}.
@@ -6002,7 +5999,7 @@
 
 # define SEL_AND_ILC_INIT_131(l) SEL_AND_ILC_INIT_128(l) , SEL_AND_ILC_INIT_2(l) , SEL_AND_ILC_INIT_1(l)
 
-	static struct { OBJ sel[nways]; struct inlineCache ilc[nways]; int flip; } sel_and_ilc[nilcs] = { SEL_AND_ILC_INIT_131(@line) };
+        static struct { OBJ sel[nways]; struct inlineCache ilc[nways]; int flip; } sel_and_ilc[nilcs] = { SEL_AND_ILC_INIT_131(@line) };
 
 # undef SEL_AND_ILC_INIT_1
 # undef SEL_AND_ILC_INIT_2
@@ -6018,38 +6015,38 @@
 # undef SEL_AND_ILC_INIT_257
 
 # define TRY(n)                                  \
-	if (sel == sel_and_ilc[hash0].sel[n]) { \
-	    pIlc = &sel_and_ilc[hash0].ilc[n];  \
-	    goto perform2_send_and_return;      \
-	}
-
-	if (__isNonNilObject(sel)) {
-	    hash0 = __MAKE_HASH__(__GET_HASH(sel)) % nilcs;
-	} else {
-	    /* sel is either nil or smallint, use its value as hash */
-	    hash0 = (INT)sel % nilcs;
-	}
-
-	TRY(0);
-	TRY(1);
+        if (sel == sel_and_ilc[hash0].sel[n]) { \
+            pIlc = &sel_and_ilc[hash0].ilc[n];  \
+            goto perform2_send_and_return;      \
+        }
+
+        if (__isNonNilObject(sel)) {
+            hash0 = __MAKE_HASH__(__GET_HASH(sel)) % nilcs;
+        } else {
+            /* sel is either nil or smallint, use its value as hash */
+            hash0 = (INT)sel % nilcs;
+        }
+
+        TRY(0);
+        TRY(1);
 
 # undef TRY
-	/*printf("Object >> #perform: #%s --> no PIC found\n", __symbolVal(aSelector));*/
-
-	pIlc = &sel_and_ilc[hash0].ilc[sel_and_ilc[hash0].flip];
-	sel_and_ilc[hash0].sel[sel_and_ilc[hash0].flip] = sel;
-	sel_and_ilc[hash0].flip = (sel_and_ilc[hash0].flip + 1) % nways;
-	pIlc->ilc_func = __SEND2ADDR__;
-	if (pIlc->ilc_poly) {
-	    __flushPolyCache(pIlc->ilc_poly);
-	    pIlc->ilc_poly = 0;
-	}
+        /*printf("Object >> #perform: #%s --> no PIC found\n", __symbolVal(aSelector));*/
+
+        pIlc = &sel_and_ilc[hash0].ilc[sel_and_ilc[hash0].flip];
+        sel_and_ilc[hash0].sel[sel_and_ilc[hash0].flip] = sel;
+        sel_and_ilc[hash0].flip = (sel_and_ilc[hash0].flip + 1) % nways;
+        pIlc->ilc_func = __SEND2ADDR__;
+        if (pIlc->ilc_poly) {
+            __flushPolyCache(pIlc->ilc_poly);
+            pIlc->ilc_poly = 0;
+        }
 
 perform2_send_and_return:
-	RETURN ( (*(pIlc->ilc_func))(self, aSelector, nil, pIlc, arg1, arg2) );
+        RETURN ( (*(pIlc->ilc_func))(self, aSelector, nil, pIlc, arg1, arg2) );
     } else {
-	static struct inlineCache ilc2 = __DUMMYILCSELF2(@line+1);
-	RETURN (_SEND2(self, aSelector, nil, &ilc2, arg1, arg2));
+        static struct inlineCache ilc2 = __DUMMYILCSELF2(@line+1);
+        RETURN (_SEND2(self, aSelector, nil, &ilc2, arg1, arg2));
     }
 #endif /* not SCHTEAM */
 %}.
@@ -6071,32 +6068,32 @@
     static int flip = 0;
 
     if (InterruptPending == nil) {
-	if (aSelector != last_0) {
-	    if (aSelector != last_1) {
-		if (flip) {
-		    pIlc = &ilc_0;
-		    flip = 0;
-		    last_0 = aSelector;
-		} else {
-		    pIlc = &ilc_1;
-		    flip = 1;
-		    last_1 = aSelector;
-		}
-		pIlc->ilc_func = __SEND3ADDR__;
-		if (pIlc->ilc_poly) {
-		    __flushPolyCache(pIlc->ilc_poly);
-		    pIlc->ilc_poly = 0;
-		}
-	    } else {
-		pIlc = &ilc_1;
-	    }
-	} else {
-	    pIlc = &ilc_0;
-	}
-	RETURN ( (*(pIlc->ilc_func))(self, aSelector, nil, pIlc, arg1, arg2, arg3) );
+        if (aSelector != last_0) {
+            if (aSelector != last_1) {
+                if (flip) {
+                    pIlc = &ilc_0;
+                    flip = 0;
+                    last_0 = aSelector;
+                } else {
+                    pIlc = &ilc_1;
+                    flip = 1;
+                    last_1 = aSelector;
+                }
+                pIlc->ilc_func = __SEND3ADDR__;
+                if (pIlc->ilc_poly) {
+                    __flushPolyCache(pIlc->ilc_poly);
+                    pIlc->ilc_poly = 0;
+                }
+            } else {
+                pIlc = &ilc_1;
+            }
+        } else {
+            pIlc = &ilc_0;
+        }
+        RETURN ( (*(pIlc->ilc_func))(self, aSelector, nil, pIlc, arg1, arg2, arg3) );
     } else {
-	static struct inlineCache ilc3 = __DUMMYILCSELF3(@line+1);
-	RETURN (_SEND3(self, aSelector, nil, &ilc3, arg1, arg2, arg3));
+        static struct inlineCache ilc3 = __DUMMYILCSELF3(@line+1);
+        RETURN (_SEND3(self, aSelector, nil, &ilc3, arg1, arg2, arg3));
     }
 #endif /* not SCHTEAM */
 %}.
@@ -6116,34 +6113,34 @@
     static int flip = 0;
 
     if (InterruptPending == nil) {
-	if (aSelector != last_0) {
-	    if (aSelector != last_1) {
-		if (flip) {
-		    pIlc = &ilc_0;
-		    flip = 0;
-		    last_0 = aSelector;
-		} else {
-		    pIlc = &ilc_1;
-		    flip = 1;
-		    last_1 = aSelector;
-		}
-		pIlc->ilc_func = __SEND4ADDR__;
-		if (pIlc->ilc_poly) {
-		    __flushPolyCache(pIlc->ilc_poly);
-		    pIlc->ilc_poly = 0;
-		}
-	    } else {
-		pIlc = &ilc_1;
-	    }
-	} else {
-	    pIlc = &ilc_0;
-	}
-	RETURN ( (*(pIlc->ilc_func))(self, aSelector, nil, pIlc,
-				     arg1, arg2, arg3, arg4) );
+        if (aSelector != last_0) {
+            if (aSelector != last_1) {
+                if (flip) {
+                    pIlc = &ilc_0;
+                    flip = 0;
+                    last_0 = aSelector;
+                } else {
+                    pIlc = &ilc_1;
+                    flip = 1;
+                    last_1 = aSelector;
+                }
+                pIlc->ilc_func = __SEND4ADDR__;
+                if (pIlc->ilc_poly) {
+                    __flushPolyCache(pIlc->ilc_poly);
+                    pIlc->ilc_poly = 0;
+                }
+            } else {
+                pIlc = &ilc_1;
+            }
+        } else {
+            pIlc = &ilc_0;
+        }
+        RETURN ( (*(pIlc->ilc_func))(self, aSelector, nil, pIlc,
+                                     arg1, arg2, arg3, arg4) );
     } else {
-	static struct inlineCache ilc4 = __DUMMYILCSELF4(@line+1);
-	RETURN (_SEND4(self, aSelector, nil, &ilc4,
-		       arg1, arg2, arg3, arg4));
+        static struct inlineCache ilc4 = __DUMMYILCSELF4(@line+1);
+        RETURN (_SEND4(self, aSelector, nil, &ilc4,
+                       arg1, arg2, arg3, arg4));
     }
 %}.
     ^ self perform:aSelector withArguments:(Array with:arg1 with:arg2 with:arg3 with:arg4)
@@ -6162,38 +6159,38 @@
     static int flip = 0;
 
     if (InterruptPending == nil) {
-	if (aSelector != last_0) {
-	    if (aSelector != last_1) {
-		if (flip) {
-		    pIlc = &ilc_0;
-		    flip = 0;
-		    last_0 = aSelector;
-		} else {
-		    pIlc = &ilc_1;
-		    flip = 1;
-		    last_1 = aSelector;
-		}
-		pIlc->ilc_func = __SEND5ADDR__;
-		if (pIlc->ilc_poly) {
-		    __flushPolyCache(pIlc->ilc_poly);
-		    pIlc->ilc_poly = 0;
-		}
-	    } else {
-		pIlc = &ilc_1;
-	    }
-	} else {
-	    pIlc = &ilc_0;
-	}
-	RETURN ( (*(pIlc->ilc_func))(self, aSelector, nil, pIlc,
-				     arg1, arg2, arg3, arg4, arg5) );
+        if (aSelector != last_0) {
+            if (aSelector != last_1) {
+                if (flip) {
+                    pIlc = &ilc_0;
+                    flip = 0;
+                    last_0 = aSelector;
+                } else {
+                    pIlc = &ilc_1;
+                    flip = 1;
+                    last_1 = aSelector;
+                }
+                pIlc->ilc_func = __SEND5ADDR__;
+                if (pIlc->ilc_poly) {
+                    __flushPolyCache(pIlc->ilc_poly);
+                    pIlc->ilc_poly = 0;
+                }
+            } else {
+                pIlc = &ilc_1;
+            }
+        } else {
+            pIlc = &ilc_0;
+        }
+        RETURN ( (*(pIlc->ilc_func))(self, aSelector, nil, pIlc,
+                                     arg1, arg2, arg3, arg4, arg5) );
     } else {
-	static struct inlineCache ilc5 = __DUMMYILCSELF5(@line+1);
-	RETURN (_SEND5(self, aSelector, nil, &ilc5,
-		       arg1, arg2, arg3, arg4, arg5));
+        static struct inlineCache ilc5 = __DUMMYILCSELF5(@line+1);
+        RETURN (_SEND5(self, aSelector, nil, &ilc5,
+                       arg1, arg2, arg3, arg4, arg5));
     }
 %}.
     ^ self perform:aSelector withArguments:(Array with:arg1 with:arg2 with:arg3 with:arg4
-						  with:arg5)
+                                                  with:arg5)
 
 !
 
@@ -6209,39 +6206,39 @@
     static int flip = 0;
 
     if (InterruptPending == nil) {
-	if (aSelector != last_0) {
-	    if (aSelector != last_1) {
-		if (flip) {
-		    pIlc = &ilc_0;
-		    flip = 0;
-		    last_0 = aSelector;
-		} else {
-		    pIlc = &ilc_1;
-		    flip = 1;
-		    last_1 = aSelector;
-		}
-		pIlc->ilc_func = __SEND6ADDR__;
-		if (pIlc->ilc_poly) {
-		    __flushPolyCache(pIlc->ilc_poly);
-		    pIlc->ilc_poly = 0;
-		}
-	    } else {
-		pIlc = &ilc_1;
-	    }
-	} else {
-	    pIlc = &ilc_0;
-	}
-
-	RETURN ( (*(pIlc->ilc_func))(self, aSelector, nil, pIlc,
-				     arg1, arg2, arg3, arg4, arg5, arg6) );
+        if (aSelector != last_0) {
+            if (aSelector != last_1) {
+                if (flip) {
+                    pIlc = &ilc_0;
+                    flip = 0;
+                    last_0 = aSelector;
+                } else {
+                    pIlc = &ilc_1;
+                    flip = 1;
+                    last_1 = aSelector;
+                }
+                pIlc->ilc_func = __SEND6ADDR__;
+                if (pIlc->ilc_poly) {
+                    __flushPolyCache(pIlc->ilc_poly);
+                    pIlc->ilc_poly = 0;
+                }
+            } else {
+                pIlc = &ilc_1;
+            }
+        } else {
+            pIlc = &ilc_0;
+        }
+
+        RETURN ( (*(pIlc->ilc_func))(self, aSelector, nil, pIlc,
+                                     arg1, arg2, arg3, arg4, arg5, arg6) );
     } else {
-	static struct inlineCache ilc6 = __DUMMYILCSELF6(@line+1);
-	RETURN (_SEND6(self, aSelector, nil, &ilc6,
-		       arg1, arg2, arg3, arg4, arg5, arg6));
+        static struct inlineCache ilc6 = __DUMMYILCSELF6(@line+1);
+        RETURN (_SEND6(self, aSelector, nil, &ilc6,
+                       arg1, arg2, arg3, arg4, arg5, arg6));
     }
 %}.
     ^ self perform:aSelector withArguments:(Array with:arg1 with:arg2 with:arg3 with:arg4
-						  with:arg5 with:arg6)
+                                                  with:arg5 with:arg6)
 
 !
 
@@ -6260,398 +6257,398 @@
     OBJ l;
 
     if (__isArrayLike(argArray)) {
-	nargs = __arraySize(argArray);
-	argP = __arrayVal(argArray);
+        nargs = __arraySize(argArray);
+        argP = __arrayVal(argArray);
     } else {
-	if (__isNonNilObject(argArray)) {
-	    static struct inlineCache ilcSize = __ILC0(@line);
-	    int i;
-
-	    numberOfArgs = (*ilcSize.ilc_func)(argArray, @symbol(size), nil, &ilcSize);
-	    if (!__isSmallInteger(numberOfArgs))
-		goto bad;
-	    nargs = __intVal(numberOfArgs);
-	    argP = (OBJ *)(&a1);
-	    for (i=1; i <= nargs; i++) {
-		*argP++ = __AT_(argArray, __mkSmallInteger(i));
-	    }
-	    argP = (OBJ *)(&a1);
-	} else {
-	    nargs = 0;
-	}
+        if (__isNonNilObject(argArray)) {
+            static struct inlineCache ilcSize = __ILC0(@line);
+            int i;
+
+            numberOfArgs = (*ilcSize.ilc_func)(argArray, @symbol(size), nil, &ilcSize);
+            if (!__isSmallInteger(numberOfArgs))
+                goto bad;
+            nargs = __intVal(numberOfArgs);
+            argP = (OBJ *)(&a1);
+            for (i=1; i <= nargs; i++) {
+                *argP++ = __AT_(argArray, __mkSmallInteger(i));
+            }
+            argP = (OBJ *)(&a1);
+        } else {
+            nargs = 0;
+        }
     }
     switch (nargs) {
-	case 0:
-	    if (InterruptPending == nil) {
-		static OBJ last0_0 = nil; static struct inlineCache ilc0_0 = __ILCPERF0(@line);
-		static OBJ last0_1 = nil; static struct inlineCache ilc0_1 = __ILCPERF0(@line);
-		static OBJ last0_2 = nil; static struct inlineCache ilc0_2 = __ILCPERF0(@line);
-		static OBJ last0_3 = nil; static struct inlineCache ilc0_3 = __ILCPERF0(@line);
-		static int flip0 = 0;
-		struct inlineCache *pIlc;
-
-		if (aSelector == last0_0) {
-		    pIlc = &ilc0_0;
-		} else if (aSelector == last0_1) {
-		    pIlc = &ilc0_1;
-		} else if (aSelector == last0_2) {
-		    pIlc = &ilc0_2;
-		} else if (aSelector == last0_3) {
-		    pIlc = &ilc0_3;
-		} else {
-		    if (flip0 == 0) {
-			pIlc = &ilc0_0;
-			flip0 = 1;
-			last0_0 = aSelector;
-		    } else if (flip0 == 1) {
-			pIlc = &ilc0_1;
-			flip0 = 2;
-			last0_1 = aSelector;
-		    } else if (flip0 == 2) {
-			pIlc = &ilc0_2;
-			flip0 = 3;
-			last0_2 = aSelector;
-		    } else {
-			pIlc = &ilc0_3;
-			flip0 = 0;
-			last0_3 = aSelector;
-		    }
-
-		    pIlc->ilc_func = __SEND0ADDR__;
-		    if (pIlc->ilc_poly) {
-			__flushPolyCache(pIlc->ilc_poly);
-			pIlc->ilc_poly = 0;
-		    }
-		}
-		RETURN ((*pIlc->ilc_func)(self, aSelector, nil, pIlc));
-	    } else {
-		static struct inlineCache ilc0 = __DUMMYILCSELF0(@line+1);
-		RETURN (_SEND0(self, aSelector, nil, &ilc0));
-	    }
-
-	case 1:
-	    if (InterruptPending == nil) {
-		static OBJ last1_0 = nil; static struct inlineCache ilc1_0 = __ILCPERF1(@line);
-		static OBJ last1_1 = nil; static struct inlineCache ilc1_1 = __ILCPERF1(@line);
-		static OBJ last1_2 = nil; static struct inlineCache ilc1_2 = __ILCPERF1(@line);
-		static OBJ last1_3 = nil; static struct inlineCache ilc1_3 = __ILCPERF1(@line);
-		static int flip1 = 0;
-		struct inlineCache *pIlc;
-
-		if (aSelector == last1_0) {
-		    pIlc = &ilc1_0;
-		} else if (aSelector == last1_1) {
-		    pIlc = &ilc1_1;
-		} else if (aSelector == last1_2) {
-		    pIlc = &ilc1_2;
-		} else if (aSelector == last1_3) {
-		    pIlc = &ilc1_3;
-		} else {
-		    if (flip1 == 0) {
-			pIlc = &ilc1_0;
-			flip1 = 1;
-			last1_0 = aSelector;
-		    } else if (flip1 == 1) {
-			pIlc = &ilc1_1;
-			flip1 = 2;
-			last1_1 = aSelector;
-		    } else if (flip1 == 2) {
-			pIlc = &ilc1_2;
-			flip1 = 3;
-			last1_2 = aSelector;
-		    } else {
-			pIlc = &ilc1_3;
-			flip1 = 0;
-			last1_3 = aSelector;
-		    }
-
-		    pIlc->ilc_func = __SEND1ADDR__;
-		    if (pIlc->ilc_poly) {
-			__flushPolyCache(pIlc->ilc_poly);
-			pIlc->ilc_poly = 0;
-		    }
-		}
-		RETURN ((*pIlc->ilc_func)(self, aSelector, nil, pIlc, argP[0]));
-	    } else {
-		static struct inlineCache ilc1 = __DUMMYILCSELF1(@line+1);
-		RETURN (_SEND1(self, aSelector, nil, &ilc1, argP[0]));
-	    }
-
-	case 2:
-	    if (InterruptPending == nil) {
-		static OBJ last2_0 = nil; static struct inlineCache ilc2_0 = __ILCPERF2(@line);
-		static OBJ last2_1 = nil; static struct inlineCache ilc2_1 = __ILCPERF2(@line);
-		static int flip2 = 0;
-		struct inlineCache *pIlc;
-
-		if (aSelector == last2_0) {
-		    pIlc = &ilc2_0;
-		} else if (aSelector == last2_1) {
-		    pIlc = &ilc2_1;
-		} else {
-		    if (flip2 == 0) {
-			pIlc = &ilc2_0;
-			flip2 = 1;
-			last2_0 = aSelector;
-		    } else {
-			pIlc = &ilc2_1;
-			flip2 = 0;
-			last2_1 = aSelector;
-		    }
-
-		    pIlc->ilc_func = __SEND2ADDR__;
-		    if (pIlc->ilc_poly) {
-			__flushPolyCache(pIlc->ilc_poly);
-			pIlc->ilc_poly = 0;
-		    }
-		}
-		RETURN ((*pIlc->ilc_func)(self, aSelector, nil, pIlc, argP[0], argP[1]));
-	    } else {
-		static struct inlineCache ilc2 = __DUMMYILCSELF2(@line+1);
-		RETURN (_SEND2(self, aSelector, nil, &ilc2, argP[0], argP[1]));
-	    }
-
-	case 3:
-	    if (InterruptPending == nil) {
-		static OBJ last3_0 = nil; static struct inlineCache ilc3_0 = __ILCPERF3(@line);
-		static OBJ last3_1 = nil; static struct inlineCache ilc3_1 = __ILCPERF3(@line);
-		static int flip3 = 0;
-		struct inlineCache *pIlc;
-
-		if (aSelector == last3_0) {
-		    pIlc = &ilc3_0;
-		} else if (aSelector == last3_1) {
-		    pIlc = &ilc3_1;
-		} else {
-		    if (flip3 == 0) {
-			pIlc = &ilc3_0;
-			flip3 = 1;
-			last3_0 = aSelector;
-		    } else {
-			pIlc = &ilc3_1;
-			flip3 = 0;
-			last3_1 = aSelector;
-		    }
-
-		    pIlc->ilc_func = __SEND3ADDR__;
-		    if (pIlc->ilc_poly) {
-			__flushPolyCache(pIlc->ilc_poly);
-			pIlc->ilc_poly = 0;
-		    }
-		}
-		RETURN ((*pIlc->ilc_func)(self, aSelector, nil, pIlc, argP[0], argP[1], argP[2]));
-	    } else {
-		static struct inlineCache ilc3 = __DUMMYILCSELF3(@line+1);
-		RETURN (_SEND3(self, aSelector, nil, &ilc3, argP[0], argP[1], argP[2]));
-	    }
-
-	case 4:
-	    {
-		static OBJ last4 = nil; static struct inlineCache ilc4 = __ILCPERF4(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last4)) {
-		    ilc4.ilc_func = __SEND4ADDR__;
-		    if (ilc4.ilc_poly) {
-			__flushPolyCache(ilc4.ilc_poly);
-			ilc4.ilc_poly = 0;
-		    }
-		    last4 = aSelector;
-		}
-		RETURN ( (*ilc4.ilc_func)(self, aSelector, nil, &ilc4,
-						argP[0], argP[1], argP[2], argP[3]));
-	    }
-
-	case 5:
-	    {
-		static OBJ last5 = nil; static struct inlineCache ilc5 = __ILCPERF5(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last5)) {
-		    ilc5.ilc_func = __SEND5ADDR__;
-		    if (ilc5.ilc_poly) {
-			__flushPolyCache(ilc5.ilc_poly);
-			ilc5.ilc_poly = 0;
-		    }
-		    last5 = aSelector;
-		}
-		RETURN ( (*ilc5.ilc_func)(self, aSelector, nil, &ilc5,
-						argP[0], argP[1], argP[2], argP[3], argP[4]));
-	    }
-
-	case 6:
-	    {
-		static OBJ last6 = nil; static struct inlineCache ilc6 = __ILCPERF6(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last6)) {
-		    ilc6.ilc_func = __SEND6ADDR__;
-		    if (ilc6.ilc_poly) {
-			__flushPolyCache(ilc6.ilc_poly);
-			ilc6.ilc_poly = 0;
-		    }
-		    last6 = aSelector;
-		}
-		RETURN ( (*ilc6.ilc_func)(self, aSelector, nil, &ilc6,
-						argP[0], argP[1], argP[2], argP[3], argP[4],
-						argP[5]));
-	    }
-
-	case 7:
-	    {
-		static OBJ last7 = nil; static struct inlineCache ilc7 = __ILCPERF7(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last7)) {
-		    ilc7.ilc_func = __SEND7ADDR__;
-		    if (ilc7.ilc_poly) {
-			__flushPolyCache(ilc7.ilc_poly);
-			ilc7.ilc_poly = 0;
-		    }
-		    last7 = aSelector;
-		}
-		RETURN ( (*ilc7.ilc_func)(self, aSelector, nil, &ilc7,
-						argP[0], argP[1], argP[2], argP[3], argP[4],
-						argP[5], argP[6]));
-	    }
-
-	case 8:
-	    {
-		static OBJ last8 = nil; static struct inlineCache ilc8 = __ILCPERF8(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last8)) {
-		    ilc8.ilc_func = __SEND8ADDR__;
-		    if (ilc8.ilc_poly) {
-			__flushPolyCache(ilc8.ilc_poly);
-			ilc8.ilc_poly = 0;
-		    }
-		    last8 = aSelector;
-		}
-		RETURN ( (*ilc8.ilc_func)(self, aSelector, nil, &ilc8,
-						argP[0], argP[1], argP[2], argP[3], argP[4],
-						argP[5], argP[6], argP[7]));
-	    }
-
-	case 9:
-	    {
-		static OBJ last9 = nil; static struct inlineCache ilc9 = __ILCPERF9(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last9)) {
-		    ilc9.ilc_func = __SEND9ADDR__;
-		    if (ilc9.ilc_poly) {
-			__flushPolyCache(ilc9.ilc_poly);
-			ilc9.ilc_poly = 0;
-		    }
-		    last9 = aSelector;
-		}
-		RETURN ( (*ilc9.ilc_func)(self, aSelector, nil, &ilc9,
-						argP[0], argP[1], argP[2], argP[3], argP[4],
-						argP[5], argP[6], argP[7], argP[8]));
-	    }
-
-	case 10:
-	    {
-		static OBJ last10 = nil; static struct inlineCache ilc10 = __ILCPERF10(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last10)) {
-		    ilc10.ilc_func = __SEND10ADDR__;
-		    if (ilc10.ilc_poly) {
-			__flushPolyCache(ilc10.ilc_poly);
-			ilc10.ilc_poly = 0;
-		    }
-		    last10 = aSelector;
-		}
-		RETURN ( (*ilc10.ilc_func)(self, aSelector, nil, &ilc10,
-						argP[0], argP[1], argP[2], argP[3], argP[4],
-						argP[5], argP[6], argP[7], argP[8], argP[9]));
-	    }
-
-	case 11:
-	    {
-		static OBJ last11 = nil; static struct inlineCache ilc11 = __ILCPERF11(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last11)) {
-		    ilc11.ilc_func = __SEND11ADDR__;
-		    if (ilc11.ilc_poly) {
-			__flushPolyCache(ilc11.ilc_poly);
-			ilc11.ilc_poly = 0;
-		    }
-		    last11 = aSelector;
-		}
-		RETURN ( (*ilc11.ilc_func)(self, aSelector, nil, &ilc11,
-						argP[0], argP[1], argP[2], argP[3], argP[4],
-						argP[5], argP[6], argP[7], argP[8], argP[9],
-						argP[10]));
-	    }
-
-	case 12:
-	    {
-		static OBJ last12 = nil; static struct inlineCache ilc12 = __ILCPERF12(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last12)) {
-		    ilc12.ilc_func = __SEND12ADDR__;
-		    if (ilc12.ilc_poly) {
-			__flushPolyCache(ilc12.ilc_poly);
-			ilc12.ilc_poly = 0;
-		    }
-		    last12 = aSelector;
-		}
-		RETURN ( (*ilc12.ilc_func)(self, aSelector, nil, &ilc12,
-						argP[0], argP[1], argP[2], argP[3], argP[4],
-						argP[5], argP[6], argP[7], argP[8], argP[9],
-						argP[10], argP[11]));
-	    }
-
-	case 13:
-	    {
-		static OBJ last13 = nil; static struct inlineCache ilc13 = __ILCPERF13(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last13)) {
-		    ilc13.ilc_func = __SEND13ADDR__;
-		    if (ilc13.ilc_poly) {
-			__flushPolyCache(ilc13.ilc_poly);
-			ilc13.ilc_poly = 0;
-		    }
-		    last13 = aSelector;
-		}
-		RETURN ( (*ilc13.ilc_func)(self, aSelector, nil, &ilc13,
-						argP[0], argP[1], argP[2], argP[3], argP[4],
-						argP[5], argP[6], argP[7], argP[8], argP[9],
-						argP[10], argP[11], argP[12]));
-	    }
-
-	case 14:
-	    {
-		static OBJ last14 = nil; static struct inlineCache ilc14 = __ILCPERF14(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last14)) {
-		    ilc14.ilc_func = __SEND14ADDR__;
-		    if (ilc14.ilc_poly) {
-			__flushPolyCache(ilc14.ilc_poly);
-			ilc14.ilc_poly = 0;
-		    }
-		    last14 = aSelector;
-		}
-		RETURN ( (*ilc14.ilc_func)(self, aSelector, nil, &ilc14,
-						argP[0], argP[1], argP[2], argP[3], argP[4],
-						argP[5], argP[6], argP[7], argP[8], argP[9],
-						argP[10], argP[11], argP[12], argP[13]));
-	    }
-
-	case 15:
-	    {
-		static OBJ last15 = nil; static struct inlineCache ilc15 = __ILCPERF15(@line);
-
-		if ((InterruptPending != nil) || (aSelector != last15)) {
-		    ilc15.ilc_func = __SEND15ADDR__;
-		    if (ilc15.ilc_poly) {
-			__flushPolyCache(ilc15.ilc_poly);
-			ilc15.ilc_poly = 0;
-		    }
-		    last15 = aSelector;
-		}
-		RETURN ( (*ilc15.ilc_func)(self, aSelector, nil, &ilc15,
-						argP[0], argP[1], argP[2], argP[3], argP[4],
-						argP[5], argP[6], argP[7], argP[8], argP[9],
-						argP[10], argP[11], argP[12], argP[13],
-						argP[14]));
-	    }
+        case 0:
+            if (InterruptPending == nil) {
+                static OBJ last0_0 = nil; static struct inlineCache ilc0_0 = __ILCPERF0(@line);
+                static OBJ last0_1 = nil; static struct inlineCache ilc0_1 = __ILCPERF0(@line);
+                static OBJ last0_2 = nil; static struct inlineCache ilc0_2 = __ILCPERF0(@line);
+                static OBJ last0_3 = nil; static struct inlineCache ilc0_3 = __ILCPERF0(@line);
+                static int flip0 = 0;
+                struct inlineCache *pIlc;
+
+                if (aSelector == last0_0) {
+                    pIlc = &ilc0_0;
+                } else if (aSelector == last0_1) {
+                    pIlc = &ilc0_1;
+                } else if (aSelector == last0_2) {
+                    pIlc = &ilc0_2;
+                } else if (aSelector == last0_3) {
+                    pIlc = &ilc0_3;
+                } else {
+                    if (flip0 == 0) {
+                        pIlc = &ilc0_0;
+                        flip0 = 1;
+                        last0_0 = aSelector;
+                    } else if (flip0 == 1) {
+                        pIlc = &ilc0_1;
+                        flip0 = 2;
+                        last0_1 = aSelector;
+                    } else if (flip0 == 2) {
+                        pIlc = &ilc0_2;
+                        flip0 = 3;
+                        last0_2 = aSelector;
+                    } else {
+                        pIlc = &ilc0_3;
+                        flip0 = 0;
+                        last0_3 = aSelector;
+                    }
+
+                    pIlc->ilc_func = __SEND0ADDR__;
+                    if (pIlc->ilc_poly) {
+                        __flushPolyCache(pIlc->ilc_poly);
+                        pIlc->ilc_poly = 0;
+                    }
+                }
+                RETURN ((*pIlc->ilc_func)(self, aSelector, nil, pIlc));
+            } else {
+                static struct inlineCache ilc0 = __DUMMYILCSELF0(@line+1);
+                RETURN (_SEND0(self, aSelector, nil, &ilc0));
+            }
+
+        case 1:
+            if (InterruptPending == nil) {
+                static OBJ last1_0 = nil; static struct inlineCache ilc1_0 = __ILCPERF1(@line);
+                static OBJ last1_1 = nil; static struct inlineCache ilc1_1 = __ILCPERF1(@line);
+                static OBJ last1_2 = nil; static struct inlineCache ilc1_2 = __ILCPERF1(@line);
+                static OBJ last1_3 = nil; static struct inlineCache ilc1_3 = __ILCPERF1(@line);
+                static int flip1 = 0;
+                struct inlineCache *pIlc;
+
+                if (aSelector == last1_0) {
+                    pIlc = &ilc1_0;
+                } else if (aSelector == last1_1) {
+                    pIlc = &ilc1_1;
+                } else if (aSelector == last1_2) {
+                    pIlc = &ilc1_2;
+                } else if (aSelector == last1_3) {
+                    pIlc = &ilc1_3;
+                } else {
+                    if (flip1 == 0) {
+                        pIlc = &ilc1_0;
+                        flip1 = 1;
+                        last1_0 = aSelector;
+                    } else if (flip1 == 1) {
+                        pIlc = &ilc1_1;
+                        flip1 = 2;
+                        last1_1 = aSelector;
+                    } else if (flip1 == 2) {
+                        pIlc = &ilc1_2;
+                        flip1 = 3;
+                        last1_2 = aSelector;
+                    } else {
+                        pIlc = &ilc1_3;
+                        flip1 = 0;
+                        last1_3 = aSelector;
+                    }
+
+                    pIlc->ilc_func = __SEND1ADDR__;
+                    if (pIlc->ilc_poly) {
+                        __flushPolyCache(pIlc->ilc_poly);
+                        pIlc->ilc_poly = 0;
+                    }
+                }
+                RETURN ((*pIlc->ilc_func)(self, aSelector, nil, pIlc, argP[0]));
+            } else {
+                static struct inlineCache ilc1 = __DUMMYILCSELF1(@line+1);
+                RETURN (_SEND1(self, aSelector, nil, &ilc1, argP[0]));
+            }
+
+        case 2:
+            if (InterruptPending == nil) {
+                static OBJ last2_0 = nil; static struct inlineCache ilc2_0 = __ILCPERF2(@line);
+                static OBJ last2_1 = nil; static struct inlineCache ilc2_1 = __ILCPERF2(@line);
+                static int flip2 = 0;
+                struct inlineCache *pIlc;
+
+                if (aSelector == last2_0) {
+                    pIlc = &ilc2_0;
+                } else if (aSelector == last2_1) {
+                    pIlc = &ilc2_1;
+                } else {
+                    if (flip2 == 0) {
+                        pIlc = &ilc2_0;
+                        flip2 = 1;
+                        last2_0 = aSelector;
+                    } else {
+                        pIlc = &ilc2_1;
+                        flip2 = 0;
+                        last2_1 = aSelector;
+                    }
+
+                    pIlc->ilc_func = __SEND2ADDR__;
+                    if (pIlc->ilc_poly) {
+                        __flushPolyCache(pIlc->ilc_poly);
+                        pIlc->ilc_poly = 0;
+                    }
+                }
+                RETURN ((*pIlc->ilc_func)(self, aSelector, nil, pIlc, argP[0], argP[1]));
+            } else {
+                static struct inlineCache ilc2 = __DUMMYILCSELF2(@line+1);
+                RETURN (_SEND2(self, aSelector, nil, &ilc2, argP[0], argP[1]));
+            }
+
+        case 3:
+            if (InterruptPending == nil) {
+                static OBJ last3_0 = nil; static struct inlineCache ilc3_0 = __ILCPERF3(@line);
+                static OBJ last3_1 = nil; static struct inlineCache ilc3_1 = __ILCPERF3(@line);
+                static int flip3 = 0;
+                struct inlineCache *pIlc;
+
+                if (aSelector == last3_0) {
+                    pIlc = &ilc3_0;
+                } else if (aSelector == last3_1) {
+                    pIlc = &ilc3_1;
+                } else {
+                    if (flip3 == 0) {
+                        pIlc = &ilc3_0;
+                        flip3 = 1;
+                        last3_0 = aSelector;
+                    } else {
+                        pIlc = &ilc3_1;
+                        flip3 = 0;
+                        last3_1 = aSelector;
+                    }
+
+                    pIlc->ilc_func = __SEND3ADDR__;
+                    if (pIlc->ilc_poly) {
+                        __flushPolyCache(pIlc->ilc_poly);
+                        pIlc->ilc_poly = 0;
+                    }
+                }
+                RETURN ((*pIlc->ilc_func)(self, aSelector, nil, pIlc, argP[0], argP[1], argP[2]));
+            } else {
+                static struct inlineCache ilc3 = __DUMMYILCSELF3(@line+1);
+                RETURN (_SEND3(self, aSelector, nil, &ilc3, argP[0], argP[1], argP[2]));
+            }
+
+        case 4:
+            {
+                static OBJ last4 = nil; static struct inlineCache ilc4 = __ILCPERF4(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last4)) {
+                    ilc4.ilc_func = __SEND4ADDR__;
+                    if (ilc4.ilc_poly) {
+                        __flushPolyCache(ilc4.ilc_poly);
+                        ilc4.ilc_poly = 0;
+                    }
+                    last4 = aSelector;
+                }
+                RETURN ( (*ilc4.ilc_func)(self, aSelector, nil, &ilc4,
+                                                argP[0], argP[1], argP[2], argP[3]));
+            }
+
+        case 5:
+            {
+                static OBJ last5 = nil; static struct inlineCache ilc5 = __ILCPERF5(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last5)) {
+                    ilc5.ilc_func = __SEND5ADDR__;
+                    if (ilc5.ilc_poly) {
+                        __flushPolyCache(ilc5.ilc_poly);
+                        ilc5.ilc_poly = 0;
+                    }
+                    last5 = aSelector;
+                }
+                RETURN ( (*ilc5.ilc_func)(self, aSelector, nil, &ilc5,
+                                                argP[0], argP[1], argP[2], argP[3], argP[4]));
+            }
+
+        case 6:
+            {
+                static OBJ last6 = nil; static struct inlineCache ilc6 = __ILCPERF6(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last6)) {
+                    ilc6.ilc_func = __SEND6ADDR__;
+                    if (ilc6.ilc_poly) {
+                        __flushPolyCache(ilc6.ilc_poly);
+                        ilc6.ilc_poly = 0;
+                    }
+                    last6 = aSelector;
+                }
+                RETURN ( (*ilc6.ilc_func)(self, aSelector, nil, &ilc6,
+                                                argP[0], argP[1], argP[2], argP[3], argP[4],
+                                                argP[5]));
+            }
+
+        case 7:
+            {
+                static OBJ last7 = nil; static struct inlineCache ilc7 = __ILCPERF7(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last7)) {
+                    ilc7.ilc_func = __SEND7ADDR__;
+                    if (ilc7.ilc_poly) {
+                        __flushPolyCache(ilc7.ilc_poly);
+                        ilc7.ilc_poly = 0;
+                    }
+                    last7 = aSelector;
+                }
+                RETURN ( (*ilc7.ilc_func)(self, aSelector, nil, &ilc7,
+                                                argP[0], argP[1], argP[2], argP[3], argP[4],
+                                                argP[5], argP[6]));
+            }
+
+        case 8:
+            {
+                static OBJ last8 = nil; static struct inlineCache ilc8 = __ILCPERF8(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last8)) {
+                    ilc8.ilc_func = __SEND8ADDR__;
+                    if (ilc8.ilc_poly) {
+                        __flushPolyCache(ilc8.ilc_poly);
+                        ilc8.ilc_poly = 0;
+                    }
+                    last8 = aSelector;
+                }
+                RETURN ( (*ilc8.ilc_func)(self, aSelector, nil, &ilc8,
+                                                argP[0], argP[1], argP[2], argP[3], argP[4],
+                                                argP[5], argP[6], argP[7]));
+            }
+
+        case 9:
+            {
+                static OBJ last9 = nil; static struct inlineCache ilc9 = __ILCPERF9(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last9)) {
+                    ilc9.ilc_func = __SEND9ADDR__;
+                    if (ilc9.ilc_poly) {
+                        __flushPolyCache(ilc9.ilc_poly);
+                        ilc9.ilc_poly = 0;
+                    }
+                    last9 = aSelector;
+                }
+                RETURN ( (*ilc9.ilc_func)(self, aSelector, nil, &ilc9,
+                                                argP[0], argP[1], argP[2], argP[3], argP[4],
+                                                argP[5], argP[6], argP[7], argP[8]));
+            }
+
+        case 10:
+            {
+                static OBJ last10 = nil; static struct inlineCache ilc10 = __ILCPERF10(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last10)) {
+                    ilc10.ilc_func = __SEND10ADDR__;
+                    if (ilc10.ilc_poly) {
+                        __flushPolyCache(ilc10.ilc_poly);
+                        ilc10.ilc_poly = 0;
+                    }
+                    last10 = aSelector;
+                }
+                RETURN ( (*ilc10.ilc_func)(self, aSelector, nil, &ilc10,
+                                                argP[0], argP[1], argP[2], argP[3], argP[4],
+                                                argP[5], argP[6], argP[7], argP[8], argP[9]));
+            }
+
+        case 11:
+            {
+                static OBJ last11 = nil; static struct inlineCache ilc11 = __ILCPERF11(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last11)) {
+                    ilc11.ilc_func = __SEND11ADDR__;
+                    if (ilc11.ilc_poly) {
+                        __flushPolyCache(ilc11.ilc_poly);
+                        ilc11.ilc_poly = 0;
+                    }
+                    last11 = aSelector;
+                }
+                RETURN ( (*ilc11.ilc_func)(self, aSelector, nil, &ilc11,
+                                                argP[0], argP[1], argP[2], argP[3], argP[4],
+                                                argP[5], argP[6], argP[7], argP[8], argP[9],
+                                                argP[10]));
+            }
+
+        case 12:
+            {
+                static OBJ last12 = nil; static struct inlineCache ilc12 = __ILCPERF12(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last12)) {
+                    ilc12.ilc_func = __SEND12ADDR__;
+                    if (ilc12.ilc_poly) {
+                        __flushPolyCache(ilc12.ilc_poly);
+                        ilc12.ilc_poly = 0;
+                    }
+                    last12 = aSelector;
+                }
+                RETURN ( (*ilc12.ilc_func)(self, aSelector, nil, &ilc12,
+                                                argP[0], argP[1], argP[2], argP[3], argP[4],
+                                                argP[5], argP[6], argP[7], argP[8], argP[9],
+                                                argP[10], argP[11]));
+            }
+
+        case 13:
+            {
+                static OBJ last13 = nil; static struct inlineCache ilc13 = __ILCPERF13(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last13)) {
+                    ilc13.ilc_func = __SEND13ADDR__;
+                    if (ilc13.ilc_poly) {
+                        __flushPolyCache(ilc13.ilc_poly);
+                        ilc13.ilc_poly = 0;
+                    }
+                    last13 = aSelector;
+                }
+                RETURN ( (*ilc13.ilc_func)(self, aSelector, nil, &ilc13,
+                                                argP[0], argP[1], argP[2], argP[3], argP[4],
+                                                argP[5], argP[6], argP[7], argP[8], argP[9],
+                                                argP[10], argP[11], argP[12]));
+            }
+
+        case 14:
+            {
+                static OBJ last14 = nil; static struct inlineCache ilc14 = __ILCPERF14(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last14)) {
+                    ilc14.ilc_func = __SEND14ADDR__;
+                    if (ilc14.ilc_poly) {
+                        __flushPolyCache(ilc14.ilc_poly);
+                        ilc14.ilc_poly = 0;
+                    }
+                    last14 = aSelector;
+                }
+                RETURN ( (*ilc14.ilc_func)(self, aSelector, nil, &ilc14,
+                                                argP[0], argP[1], argP[2], argP[3], argP[4],
+                                                argP[5], argP[6], argP[7], argP[8], argP[9],
+                                                argP[10], argP[11], argP[12], argP[13]));
+            }
+
+        case 15:
+            {
+                static OBJ last15 = nil; static struct inlineCache ilc15 = __ILCPERF15(@line);
+
+                if ((InterruptPending != nil) || (aSelector != last15)) {
+                    ilc15.ilc_func = __SEND15ADDR__;
+                    if (ilc15.ilc_poly) {
+                        __flushPolyCache(ilc15.ilc_poly);
+                        ilc15.ilc_poly = 0;
+                    }
+                    last15 = aSelector;
+                }
+                RETURN ( (*ilc15.ilc_func)(self, aSelector, nil, &ilc15,
+                                                argP[0], argP[1], argP[2], argP[3], argP[4],
+                                                argP[5], argP[6], argP[7], argP[8], argP[9],
+                                                argP[10], argP[11], argP[12], argP[13],
+                                                argP[14]));
+            }
     }
 bad:;
 #endif
@@ -6668,7 +6665,7 @@
      If the message expects an argument, pass arg."
 
     aSelector argumentCount == 1 ifTrue:[
-	^ self perform:aSelector with:arg
+        ^ self perform:aSelector with:arg
     ].
     ^ self perform:aSelector
 
@@ -6693,10 +6690,10 @@
 
     numArgs := aSelector argumentCount.
     numArgs == 0 ifTrue:[
-	^ self perform:aSelector
+        ^ self perform:aSelector
     ].
     numArgs == 1 ifTrue:[
-	^ self perform:aSelector with:optionalArg1
+        ^ self perform:aSelector with:optionalArg1
     ].
     ^ self perform:aSelector with:optionalArg1 with:optionalArg2.
 
@@ -6721,13 +6718,13 @@
 
     numArgs := aSelector argumentCount.
     numArgs == 0 ifTrue:[
-	^ self perform:aSelector
+        ^ self perform:aSelector
     ].
     numArgs == 1 ifTrue:[
-	^ self perform:aSelector with:optionalArg1
+        ^ self perform:aSelector with:optionalArg1
     ].
     numArgs == 2 ifTrue:[
-	^ self perform:aSelector with:optionalArg1 with:optionalArg2
+        ^ self perform:aSelector with:optionalArg1 with:optionalArg2
     ].
     ^ self perform:aSelector with:optionalArg1 with:optionalArg2 with:optionalArg3.
 
@@ -6752,16 +6749,16 @@
 
     numArgs := aSelector argumentCount.
     numArgs == 0 ifTrue:[
-	^ self perform:aSelector
+        ^ self perform:aSelector
     ].
     numArgs == 1 ifTrue:[
-	^ self perform:aSelector with:optionalArg1
+        ^ self perform:aSelector with:optionalArg1
     ].
     numArgs == 2 ifTrue:[
-	^ self perform:aSelector with:optionalArg1 with:optionalArg2
+        ^ self perform:aSelector with:optionalArg1 with:optionalArg2
     ].
     numArgs == 3 ifTrue:[
-	^ self perform:aSelector with:optionalArg1 with:optionalArg2 with:optionalArg3
+        ^ self perform:aSelector with:optionalArg1 with:optionalArg2 with:optionalArg3
     ].
     ^ self perform:aSelector with:optionalArg1 with:optionalArg2 with:optionalArg3 with:optionalArg4.
 
@@ -6795,8 +6792,8 @@
      This is a non-object-oriented entry, applying a method
      in a functional way on a receiver.
      Warning:
-	 Take care for the method to be appropriate for the
-	 receiver - no checking is done by the VM."
+         Take care for the method to be appropriate for the
+         receiver - no checking is done by the VM."
 
     ^ aMethod valueWithReceiver:self arguments:#()
 
@@ -6825,8 +6822,8 @@
      This is a non-object-oriented entry, applying a method
      in a functional way on a receiver.
      Warning:
-	 Take care for the method to be appropriate for the
-	 receiver - no checking is done by the VM."
+         Take care for the method to be appropriate for the
+         receiver - no checking is done by the VM."
 
     ^ aMethod valueWithReceiver:self arguments:argumentArray
 
@@ -6846,8 +6843,8 @@
      This is a non-object-oriented entry, applying a method
      in a functional way on a receiver.
      Warning:
-	 Take care for the method to be appropriate for the
-	 receiver - no checking is done by the VM."
+         Take care for the method to be appropriate for the
+         receiver - no checking is done by the VM."
 
     ^ aMethod valueWithReceiver:self arguments:(Array with:arg)
 
@@ -6867,8 +6864,8 @@
      This is a non-object-oriented entry, applying a method
      in a functional way on a receiver.
      Warning:
-	 Take care for the method to be appropriate for the
-	 receiver - no checking is done by the VM."
+         Take care for the method to be appropriate for the
+         receiver - no checking is done by the VM."
 
     ^ aMethod valueWithReceiver:self arguments:(Array with:arg1 with:arg2)
 
@@ -6890,8 +6887,8 @@
      This is a non-object-oriented entry, applying a method
      in a functional way on a receiver.
      Warning:
-	 Take care for the method to be appropriate for the
-	 receiver - no checking is done by the VM."
+         Take care for the method to be appropriate for the
+         receiver - no checking is done by the VM."
 
     ^ aMethod valueWithReceiver:self arguments:(Array with:arg1 with:arg2 with:arg3)
 
@@ -6908,7 +6905,7 @@
     REGISTER OBJ sel = aSelector;
 
     if (InterruptPending == nil) {
-	struct inlineCache *pIlc;
+        struct inlineCache *pIlc;
 
 #define SEL_AND_ILC_INIT_1(l)   { nil , __ILCPERF0(l) }
 #define SEL_AND_ILC_INIT_2(l)   SEL_AND_ILC_INIT_1(l)   , SEL_AND_ILC_INIT_1(l)
@@ -6923,11 +6920,11 @@
 #undef nilcs
 #define nilcs 256
 
-	static struct sel_and_ilc {
-	    OBJ sel;
-	    struct inlineCache ilc;
-	    struct sel_and_ilc *next;
-	} sel_and_ilc[nilcs] = { SEL_AND_ILC_INIT_256(29) };
+        static struct sel_and_ilc {
+            OBJ sel;
+            struct inlineCache ilc;
+            struct sel_and_ilc *next;
+        } sel_and_ilc[nilcs] = { SEL_AND_ILC_INIT_256(29) };
 
 #undef SEL_AND_ILC_INIT_1
 #undef SEL_AND_ILC_INIT_2
@@ -6939,62 +6936,62 @@
 #undef SEL_AND_ILC_INIT_128
 #undef SEL_AND_ILC_INIT_256
 
-	static struct sel_and_ilc *nextFree = sel_and_ilc;
-	static struct sel_and_ilc *lastUsed = 0;
-	int n;
-	struct sel_and_ilc *slot, *prev, *prevPrev;
-
-	for (n=0, slot = lastUsed, prev = prevPrev = 0; slot; n++, slot = slot->next) {
-	   if (sel == slot->sel) {
+        static struct sel_and_ilc *nextFree = sel_and_ilc;
+        static struct sel_and_ilc *lastUsed = 0;
+        int n;
+        struct sel_and_ilc *slot, *prev, *prevPrev;
+
+        for (n=0, slot = lastUsed, prev = prevPrev = 0; slot; n++, slot = slot->next) {
+           if (sel == slot->sel) {
 #ifdef XXDEBUG
 printf("cached slot %d (len=%d)\n", slot-sel_and_ilc, n);
 #endif
-		pIlc = &(slot->ilc);
-		// move to front
-		if (prev) {
-		    prev->next = slot->next;
-		}
-		slot->next = lastUsed;
-		lastUsed = slot;
-		pIlc = &(slot->ilc);
-		goto perform0_send_and_return;
-	   }
-	   prevPrev = prev;
-	   prev = slot;
-	}
-	// not recently used...
-	if (nextFree) {
-	    // another free one
-	    slot = nextFree;
-	    nextFree = nextFree + 1;
-	    if (nextFree >= &(sel_and_ilc[nilcs])) nextFree = 0;
+                pIlc = &(slot->ilc);
+                // move to front
+                if (prev) {
+                    prev->next = slot->next;
+                }
+                slot->next = lastUsed;
+                lastUsed = slot;
+                pIlc = &(slot->ilc);
+                goto perform0_send_and_return;
+           }
+           prevPrev = prev;
+           prev = slot;
+        }
+        // not recently used...
+        if (nextFree) {
+            // another free one
+            slot = nextFree;
+            nextFree = nextFree + 1;
+            if (nextFree >= &(sel_and_ilc[nilcs])) nextFree = 0;
 #ifdef XXDEBUG
 printf("new slot %d\n", slot-sel_and_ilc);
 #endif
-	} else {
-	    // no more for reuse - use least recently used
-	    slot = prev;
-	    prevPrev->next = 0;
-	    slot->next = lastUsed;
-	    lastUsed = slot;
+        } else {
+            // no more for reuse - use least recently used
+            slot = prev;
+            prevPrev->next = 0;
+            slot->next = lastUsed;
+            lastUsed = slot;
 #ifdef XXDEBUG
 printf("reuse last slot %d\n", slot-sel_and_ilc);
 #endif
-	}
-
-	/*printf("Object >> #perform: #%s --> no PIC found\n", __symbolVal(aSelector));*/
-	pIlc = &(slot->ilc);
-	slot->sel = sel;
-	pIlc->ilc_func = __SEND0ADDR__;
-	if (pIlc->ilc_poly) {
-	     __flushPolyCache(pIlc->ilc_poly);
-	    pIlc->ilc_poly = 0;
-	}
+        }
+
+        /*printf("Object >> #perform: #%s --> no PIC found\n", __symbolVal(aSelector));*/
+        pIlc = &(slot->ilc);
+        slot->sel = sel;
+        pIlc->ilc_func = __SEND0ADDR__;
+        if (pIlc->ilc_poly) {
+             __flushPolyCache(pIlc->ilc_poly);
+            pIlc->ilc_poly = 0;
+        }
 perform0_send_and_return:
-	RETURN ( (*(pIlc->ilc_func))(self, sel, nil, pIlc) );
+        RETURN ( (*(pIlc->ilc_func))(self, sel, nil, pIlc) );
     } else {
-	static struct inlineCache ilc0 = __DUMMYILCSELF0(@line+1);
-	RETURN (_SEND0(self, aSelector, nil, &ilc0));
+        static struct inlineCache ilc0 = __DUMMYILCSELF0(@line+1);
+        RETURN (_SEND0(self, aSelector, nil, &ilc0));
     }
 %}.
     ^ self perform:aSelector withArguments:#()
@@ -7009,7 +7006,7 @@
     REGISTER OBJ sel = aSelector;
 
     if (InterruptPending == nil) {
-	struct inlineCache *pIlc;
+        struct inlineCache *pIlc;
     /* JV @ 2010-22-07: To improve performance I use 256 ILCs instead
        of default 4. For details, see comment in perform: */
 
@@ -7026,7 +7023,7 @@
 #undef nilcs
 #define nilcs 256
 
-	static struct { OBJ sel; struct inlineCache ilc; } sel_and_ilc[nilcs] = { SEL_AND_ILC_INIT_256(29) };
+        static struct { OBJ sel; struct inlineCache ilc; } sel_and_ilc[nilcs] = { SEL_AND_ILC_INIT_256(29) };
 
 #undef SEL_AND_ILC_INIT_1
 #undef SEL_AND_ILC_INIT_2
@@ -7038,28 +7035,28 @@
 #undef SEL_AND_ILC_INIT_128
 #undef SEL_AND_ILC_INIT_256
 
-	static int flip = 0;
-	int i;
-	for (i = 0; i < nilcs; i++) {
-	   if (sel == sel_and_ilc[i].sel) {
-		pIlc = &sel_and_ilc[i].ilc;
-		goto perform1_send_and_return;
-	   }
-	}
-	/*printf("Object >> #perform: #%s with: arg --> no PIC found\n", __symbolVal(aSelector));*/
-	pIlc = &sel_and_ilc[flip].ilc;
-	sel_and_ilc[flip].sel = sel;
-	flip = (flip + 1) % nilcs;
-	pIlc->ilc_func = __SEND1ADDR__;
-	if (pIlc->ilc_poly) {
-	     __flushPolyCache(pIlc->ilc_poly);
-	    pIlc->ilc_poly = 0;
-	}
+        static int flip = 0;
+        int i;
+        for (i = 0; i < nilcs; i++) {
+           if (sel == sel_and_ilc[i].sel) {
+                pIlc = &sel_and_ilc[i].ilc;
+                goto perform1_send_and_return;
+           }
+        }
+        /*printf("Object >> #perform: #%s with: arg --> no PIC found\n", __symbolVal(aSelector));*/
+        pIlc = &sel_and_ilc[flip].ilc;
+        sel_and_ilc[flip].sel = sel;
+        flip = (flip + 1) % nilcs;
+        pIlc->ilc_func = __SEND1ADDR__;
+        if (pIlc->ilc_poly) {
+             __flushPolyCache(pIlc->ilc_poly);
+            pIlc->ilc_poly = 0;
+        }
 perform1_send_and_return:
-	RETURN ( (*(pIlc->ilc_func))(self, sel, nil, pIlc, arg) );
+        RETURN ( (*(pIlc->ilc_func))(self, sel, nil, pIlc, arg) );
     } else {
-	static struct inlineCache ilc1 = __DUMMYILCSELF1(@line+1);
-	RETURN (_SEND1(self, aSelector, nil, &ilc1, arg));
+        static struct inlineCache ilc1 = __DUMMYILCSELF1(@line+1);
+        RETURN (_SEND1(self, aSelector, nil, &ilc1, arg));
     }
 %}.
     ^ self perform:aSelector withArguments:(Array with:arg)
@@ -7094,10 +7091,10 @@
 
     ret := 0.
     anAspectSymbol notNil ifTrue:[
-	ret := self perform:anAspectSymbol ifNotUnderstood:[0].
+        ret := self perform:anAspectSymbol ifNotUnderstood:[0].
     ].
     ret == 0 ifTrue:[
-	^ self elementDescriptorForNonNilInstanceVariables
+        ^ self elementDescriptorForNonNilInstanceVariables
     ].
     ^ ret.
 !
@@ -7130,16 +7127,16 @@
 
     instVarNames := theClass allInstVarNames.
     1 to:instSize do:[:i | |var|
-	var := self instVarAt:i.
-	(aBlock value:var) ifTrue:[
-	    children add:((instVarNames at:i) -> var)
-	]
+        var := self instVarAt:i.
+        (aBlock value:var) ifTrue:[
+            children add:((instVarNames at:i) -> var)
+        ]
     ].
 
     varSize ~~ 0 ifTrue:[
-	1 to:varSize do:[:i |
-	    children add:(i -> (self basicAt:i))
-	]
+        1 to:varSize do:[:i |
+            children add:(i -> (self basicAt:i))
+        ]
     ].
 
     ^ children.
@@ -7198,10 +7195,10 @@
     | cls|
 
     (cls := self class) == self ifTrue:[
-	^ 'a funny object'
+        ^ 'a funny object'
     ].
     cls isNil ifTrue:[
-	^ 'a nil-classes object'        "/ cannot happen
+        ^ 'a nil-classes object'        "/ cannot happen
     ].
     ^ cls nameWithArticle
 
@@ -7222,7 +7219,7 @@
      headless applications."
 
     Logger notNil ifTrue:[
-        PartialErrorPrintLine := (PartialErrorPrintLine ? ''),self asString.
+        PartialErrorPrintLine := (PartialErrorPrintLine ? ''), self printString string.
         ^ self.
     ].
     Stderr isNil ifTrue:[
@@ -7248,7 +7245,7 @@
 
     Logger notNil ifTrue:[
         |fullLine|
-        fullLine := (PartialErrorPrintLine ? ''),self asString.
+        fullLine := (PartialErrorPrintLine ? ''), self printString string.
         PartialErrorPrintLine := nil.
         Logger error:fullLine.
         ^ self.
@@ -7304,7 +7301,7 @@
      These messages can be turned on/off by 'Object infoPrinting:true/false'"
 
     Logger notNil ifTrue:[
-        PartialInfoPrintLine := (PartialInfoPrintLine ? ''),self asString.
+        PartialInfoPrintLine := (PartialInfoPrintLine ? ''), self printString string.
         ^ self.
     ].
     
@@ -7328,7 +7325,7 @@
 
     Logger notNil ifTrue:[
         |fullLine|
-        fullLine := (PartialInfoPrintLine ? ''),self asString.
+        fullLine := (PartialInfoPrintLine ? ''), self printString string.
         PartialInfoPrintLine := nil.
         Logger info:fullLine.
         ^ self.
@@ -7350,6 +7347,22 @@
     ^ self infoPrintCR
 !
 
+lowLevelErrorPrint
+    "do not use this directly.
+     Prints on stderr, regardless of any redirection to a logger.
+     Only to be used by the MiniDebugger, to ensure that its output is shown to a user"
+
+    self asString lowLevelErrorPrint.
+!
+
+lowLevelErrorPrintCR
+    "do not use this directly.
+     Prints on stderr, regardless of any redirection to a logger.
+     Only to be used by the MiniDebugger, to ensure that its output is shown to a user"
+
+    self asString lowLevelErrorPrintCR.
+!
+
 print
     "print the receiver on the standard output stream (which is not the Transcript)"
 
@@ -7358,8 +7371,8 @@
     "/ (depends on String to respond to #print, without recurring back to here)
 
     Stdout isNil ifTrue:[
-	self printString utf8Encoded print.
-	^ self
+        self printString utf8Encoded print.
+        ^ self
     ].
     self printOn:Processor activeProcess stdout
 
@@ -7376,8 +7389,8 @@
     |stdout|
 
     Stdout isNil ifTrue:[
-	self printString utf8Encoded printCR.
-	^ self
+        self printString utf8Encoded printCR.
+        ^ self
     ].
     stdout := Processor activeProcess stdout.
     self printOn:stdout.
@@ -7609,9 +7622,9 @@
     |rslt|
 
     Error handle:[:ex |
-	rslt := exceptionBlock value
+        rslt := exceptionBlock value
     ] do:[
-	rslt := self printString
+        rslt := self printString
     ].
     ^ rslt
 !
@@ -7755,12 +7768,12 @@
     |myClass hasSemi sz "{ Class: SmallInteger }" |
 
     thisContext isRecursive ifTrue:[
-	RecursiveStoreError raiseRequestWith:self.
-	'Object [error]: storeString of self referencing object (' errorPrint.
-	self class name errorPrint.
-	')' errorPrintCR.
-	aStream nextPutAll:'#("recursive")'.
-	^ self
+        RecursiveStoreError raiseRequestWith:self.
+        'Object [error]: storeString of self referencing object (' errorPrint.
+        self class name errorPrint.
+        ')' errorPrintCR.
+        aStream nextPutAll:'#("recursive")'.
+        ^ self
     ].
 
     myClass := self class.
@@ -7769,48 +7782,48 @@
 
     hasSemi := false.
     myClass isVariable ifTrue:[
-	aStream nextPutAll:' basicNew:'.
-	self basicSize printOn:aStream
+        aStream nextPutAll:' basicNew:'.
+        self basicSize printOn:aStream
     ] ifFalse:[
-	aStream nextPutAll:' basicNew'
+        aStream nextPutAll:' basicNew'
     ].
 
     sz := myClass instSize.
     1 to:sz do:[:i |
-	|ref|
-
-	ref := (self instVarAt:i).
-	"/ no need to store nil entries, because the object has been instantiated
-	"/ with basicNew just a moment ago (so the fields are already nil)
-	ref notNil ifTrue:[
-	    aStream nextPutAll:' instVarAt:'.
-	    i printOn:aStream.
-	    aStream nextPutAll:' put:'.
-	    ref storeOn:aStream.
-	    aStream nextPut:$;.
-	    hasSemi := true
-	].
+        |ref|
+
+        ref := (self instVarAt:i).
+        "/ no need to store nil entries, because the object has been instantiated
+        "/ with basicNew just a moment ago (so the fields are already nil)
+        ref notNil ifTrue:[
+            aStream nextPutAll:' instVarAt:'.
+            i printOn:aStream.
+            aStream nextPutAll:' put:'.
+            ref storeOn:aStream.
+            aStream nextPut:$;.
+            hasSemi := true
+        ].
     ].
     myClass isVariable ifTrue:[
-	sz := self basicSize.
-	1 to:sz do:[:i |
-	    |ref|
-
-	    ref := (self basicAt:i).
-	    "/ no need to store nil entries, because the object has been instantiated
-	    "/ with basicNew just a moment ago (so the fields are already nil)
-	    ref notNil ifTrue:[
-		aStream nextPutAll:' basicAt:'.
-		i printOn:aStream.
-		aStream nextPutAll:' put:'.
-		ref storeOn:aStream.
-		aStream nextPut:$;.
-		hasSemi := true
-	    ]
-	]
+        sz := self basicSize.
+        1 to:sz do:[:i |
+            |ref|
+
+            ref := (self basicAt:i).
+            "/ no need to store nil entries, because the object has been instantiated
+            "/ with basicNew just a moment ago (so the fields are already nil)
+            ref notNil ifTrue:[
+                aStream nextPutAll:' basicAt:'.
+                i printOn:aStream.
+                aStream nextPutAll:' put:'.
+                ref storeOn:aStream.
+                aStream nextPut:$;.
+                hasSemi := true
+            ]
+        ]
     ].
     hasSemi ifTrue:[
-	aStream nextPutAll:' yourself'
+        aStream nextPutAll:' yourself'
     ].
     aStream nextPut:$).
 
@@ -7881,19 +7894,19 @@
     (Smalltalk isInitialized
     and:[ UserPreferences notNil
     and:[ UserPreferences current sendMessagesAlsoToTranscript]]) ifTrue:[
-	stream := activeProcess isSystemProcess
-			    ifTrue:[stderr]
-			    ifFalse:[activeProcess transcript].
+        stream := activeProcess isSystemProcess
+                            ifTrue:[stderr]
+                            ifFalse:[activeProcess transcript].
     ].
     stream notNil ifTrue:[
-	StreamError catch:[
-	    aBlock value:stream.
-	].
+        StreamError catch:[
+            aBlock value:stream.
+        ].
     ].
     stream ~~ stderr ifTrue:[
-	UserPreferences current sendMessagesOnlyToTranscript ifFalse:[
-	    aBlock value:stderr.
-	].
+        UserPreferences current sendMessagesOnlyToTranscript ifFalse:[
+            aBlock value:stderr.
+        ].
     ].
 
     "Created: / 21-04-2011 / 12:46:21 / cg"
@@ -7925,46 +7938,46 @@
     nInstBytes = OHDR_SIZE + __OBJS2BYTES__( __intVal(__ClassInstPtr(myClass)->c_ninstvars) );
 
     switch ((INT)(__ClassInstPtr(myClass)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
-	case __MASKSMALLINT(POINTERARRAY):
-	case __MASKSMALLINT(WKPOINTERARRAY):
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(__BYTES2OBJS__(nbytes)) );
-
-	case __MASKSMALLINT(BYTEARRAY):
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes / sizeof(char)) );
-
-	case __MASKSMALLINT(FLOATARRAY):
+        case __MASKSMALLINT(POINTERARRAY):
+        case __MASKSMALLINT(WKPOINTERARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(__BYTES2OBJS__(nbytes)) );
+
+        case __MASKSMALLINT(BYTEARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes / sizeof(char)) );
+
+        case __MASKSMALLINT(FLOATARRAY):
 # ifdef __NEED_FLOATARRAY_ALIGN
-	    nInstBytes = (nInstBytes-1+__FLOATARRAY_ALIGN) &~ (__FLOATARRAY_ALIGN-1);
+            nInstBytes = (nInstBytes-1+__FLOATARRAY_ALIGN) &~ (__FLOATARRAY_ALIGN-1);
 # endif
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes / sizeof(float)) );
-
-	case __MASKSMALLINT(DOUBLEARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes / sizeof(float)) );
+
+        case __MASKSMALLINT(DOUBLEARRAY):
 # ifdef __NEED_DOUBLE_ALIGN
-	    nInstBytes = (nInstBytes-1+__DOUBLE_ALIGN) &~ (__DOUBLE_ALIGN-1);
+            nInstBytes = (nInstBytes-1+__DOUBLE_ALIGN) &~ (__DOUBLE_ALIGN-1);
 # endif
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes / sizeof(double)) );
-
-	case __MASKSMALLINT(WORDARRAY):
-	case __MASKSMALLINT(SWORDARRAY):
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes>>1) ); /* notice the hardcoded 2 here - not sizeof(short) */
-
-	case __MASKSMALLINT(LONGARRAY):
-	case __MASKSMALLINT(SLONGARRAY):
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes>>2) ); /* notice the hardcoded 4 here - not sizeof(int) */
-
-	case __MASKSMALLINT(LONGLONGARRAY):
-	case __MASKSMALLINT(SLONGLONGARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes / sizeof(double)) );
+
+        case __MASKSMALLINT(WORDARRAY):
+        case __MASKSMALLINT(SWORDARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes>>1) ); /* notice the hardcoded 2 here - not sizeof(short) */
+
+        case __MASKSMALLINT(LONGARRAY):
+        case __MASKSMALLINT(SLONGARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes>>2) ); /* notice the hardcoded 4 here - not sizeof(int) */
+
+        case __MASKSMALLINT(LONGLONGARRAY):
+        case __MASKSMALLINT(SLONGLONGARRAY):
 # ifdef __NEED_LONGLONG_ALIGN
-	    nInstBytes = (nInstBytes-1+__LONGLONG_ALIGN) &~ (__LONGLONG_ALIGN-1);
+            nInstBytes = (nInstBytes-1+__LONGLONG_ALIGN) &~ (__LONGLONG_ALIGN-1);
 # endif
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes>>3) ); /* notice the hardcoded 8 here - not sizeof(long long) */
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes>>3) ); /* notice the hardcoded 8 here - not sizeof(long long) */
     }
 #endif /* not __SCHTEAM__ */
 %}.
@@ -7982,36 +7995,36 @@
 
     myClass := self class.
     myClass isVariable ifTrue:[
-	myClass isPointers ifFalse:[
-	    myClass isBytes ifTrue:[
-		^ self basicSize.
-	    ].
-	    myClass isWords ifTrue:[
-		^ self basicSize * 2.
-	    ].
-	    myClass isSignedWords ifTrue:[
-		^ self basicSize * 2.
-	    ].
-	    myClass isLongs ifTrue:[
-		^ self basicSize * 4.
-	    ].
-	    myClass isSignedLongs ifTrue:[
-		^ self basicSize * 4.
-	    ].
-	    myClass isLongLongs ifTrue:[
-		^ self basicSize * 8.
-	    ].
-	    myClass isSignedLongLongs ifTrue:[
-		^ self basicSize * 8.
-	    ].
-	    myClass isFloats ifTrue:[
-		^ self basicSize * (ExternalBytes sizeofFloat)
-	    ].
-	    myClass isDoubles ifTrue:[
-		^ self basicSize * (ExternalBytes sizeofDouble)
-	    ].
-	    self error:'unknown variable size class species'.
-	]
+        myClass isPointers ifFalse:[
+            myClass isBytes ifTrue:[
+                ^ self basicSize.
+            ].
+            myClass isWords ifTrue:[
+                ^ self basicSize * 2.
+            ].
+            myClass isSignedWords ifTrue:[
+                ^ self basicSize * 2.
+            ].
+            myClass isLongs ifTrue:[
+                ^ self basicSize * 4.
+            ].
+            myClass isSignedLongs ifTrue:[
+                ^ self basicSize * 4.
+            ].
+            myClass isLongLongs ifTrue:[
+                ^ self basicSize * 8.
+            ].
+            myClass isSignedLongLongs ifTrue:[
+                ^ self basicSize * 8.
+            ].
+            myClass isFloats ifTrue:[
+                ^ self basicSize * (ExternalBytes sizeofFloat)
+            ].
+            myClass isDoubles ifTrue:[
+                ^ self basicSize * (ExternalBytes sizeofDouble)
+            ].
+            self error:'unknown variable size class species'.
+        ]
     ].
     ^ 0
 
@@ -8058,7 +8071,7 @@
 %{  /* NOCONTEXT */
 
     if (__lookup(__Class(self), aSelector) == nil) {
-	RETURN ( false );
+        RETURN ( false );
     }
     RETURN ( true );
 %}
@@ -8172,17 +8185,17 @@
     |val ok|
 
     MessageNotUnderstood handle:[:ex |
-	"/ reject, if the bad message is not the one
-	"/ we have sent originally
-	(ex selector == aSelector and:[ex receiver == self]) ifFalse:[
-	    ex reject
-	].
+        "/ reject, if the bad message is not the one
+        "/ we have sent originally
+        (ex selector == aSelector and:[ex receiver == self]) ifFalse:[
+            ex reject
+        ].
     ] do:[
-	val := self perform:aSelector.
-	ok := true.
+        val := self perform:aSelector.
+        ok := true.
     ].
     ok isNil ifTrue:[
-	^ exceptionBlock value
+        ^ exceptionBlock value
     ].
     ^ val
 
@@ -8206,17 +8219,17 @@
     |val ok|
 
     MessageNotUnderstood handle:[:ex |
-	"/ reject, if the bad message is not the one
-	"/ we have sent originally
-	(ex selector == aSelector and:[ex receiver == self]) ifFalse:[
-	    ex reject
-	]
+        "/ reject, if the bad message is not the one
+        "/ we have sent originally
+        (ex selector == aSelector and:[ex receiver == self]) ifFalse:[
+            ex reject
+        ]
     ] do:[
-	val := self perform:aSelector with:argument.
-	ok := true.
+        val := self perform:aSelector with:argument.
+        ok := true.
     ].
     ok isNil ifTrue:[
-	^ exceptionBlock value
+        ^ exceptionBlock value
     ].
     ^ val
 
@@ -8243,17 +8256,17 @@
     |val ok|
 
     MessageNotUnderstood handle:[:ex |
-	"/ reject, if the bad message is not the one
-	"/ we have sent originally
-	(ex selector == aSelector and:[ex receiver == self]) ifFalse:[
-	    ex reject
-	]
+        "/ reject, if the bad message is not the one
+        "/ we have sent originally
+        (ex selector == aSelector and:[ex receiver == self]) ifFalse:[
+            ex reject
+        ]
     ] do:[
-	val := self perform:aSelector with:arg1 with:arg2.
-	ok := true.
+        val := self perform:aSelector with:arg1 with:arg2.
+        ok := true.
     ].
     ok isNil ifTrue:[
-	^ exceptionBlock value
+        ^ exceptionBlock value
     ].
     ^ val
 !
@@ -8271,17 +8284,17 @@
     |val ok|
 
     MessageNotUnderstood handle:[:ex |
-	"/ reject, if the bad message is not the one
-	"/ we have sent originally.
-	(ex selector == aSelector and:[ex receiver == self]) ifFalse:[
-	    ex reject
-	]
+        "/ reject, if the bad message is not the one
+        "/ we have sent originally.
+        (ex selector == aSelector and:[ex receiver == self]) ifFalse:[
+            ex reject
+        ]
     ] do:[
-	val := self perform:aSelector withArguments:argumentArray.
-	ok := true.
+        val := self perform:aSelector withArguments:argumentArray.
+        ok := true.
     ].
     ok isNil ifTrue:[
-	^ exceptionBlock value
+        ^ exceptionBlock value
     ].
     ^ val
 
@@ -8337,152 +8350,152 @@
     int nInsts, inst;
 
     if (! __isNonNilObject(self)) {
-	RETURN (false);
+        RETURN (false);
     }
 
     if (__isArrayLike(aCollection)) {
-	int nObjs = __arraySize(aCollection);
-	char *minAddr = 0, *maxAddr = 0;
-
-	if (nObjs == 0) {
-	    RETURN (false);
-	}
-
-	cls = __qClass(self);
-	flags = __ClassInstPtr(cls)->c_flags;
-	if (((INT)flags & __MASKSMALLINT(ARRAYMASK)) == __MASKSMALLINT(POINTERARRAY)) {
-	    nInsts = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
-	} else {
-	    nInsts = __intVal(__ClassInstPtr(cls)->c_ninstvars);
-	}
-
-	if (nObjs == 1) {
-	    /* better reverse the loop */
-	    OBJ anObject = __arrayVal(aCollection)[0];
-
-	    if (anObject == cls) {
-		RETURN(true);
-	    }
-	    if (! nInsts) {
-		RETURN (false);
-	    }
-
-	    if ((__qSpace(self) <= OLDSPACE)
-		    && !__isRemembered(self)
-		    && __isNonNilObject(anObject)) {
-		int spc = __qSpace(anObject);
-
-		if ((spc == NEWSPACE) || (spc == SURVSPACE)) {
-		    RETURN(false);
-		}
-	    }
+        int nObjs = __arraySize(aCollection);
+        char *minAddr = 0, *maxAddr = 0;
+
+        if (nObjs == 0) {
+            RETURN (false);
+        }
+
+        cls = __qClass(self);
+        flags = __ClassInstPtr(cls)->c_flags;
+        if (((INT)flags & __MASKSMALLINT(ARRAYMASK)) == __MASKSMALLINT(POINTERARRAY)) {
+            nInsts = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
+        } else {
+            nInsts = __intVal(__ClassInstPtr(cls)->c_ninstvars);
+        }
+
+        if (nObjs == 1) {
+            /* better reverse the loop */
+            OBJ anObject = __arrayVal(aCollection)[0];
+
+            if (anObject == cls) {
+                RETURN(true);
+            }
+            if (! nInsts) {
+                RETURN (false);
+            }
+
+            if ((__qSpace(self) <= OLDSPACE)
+                    && !__isRemembered(self)
+                    && __isNonNilObject(anObject)) {
+                int spc = __qSpace(anObject);
+
+                if ((spc == NEWSPACE) || (spc == SURVSPACE)) {
+                    RETURN(false);
+                }
+            }
 
 # if defined(memsrch4)
-	    if (memsrch4(__InstPtr(self)->i_instvars, (INT)anObject, nInsts)) {
-		RETURN (true);
-	    }
+            if (memsrch4(__InstPtr(self)->i_instvars, (INT)anObject, nInsts)) {
+                RETURN (true);
+            }
 # else
-	    for (inst=0; inst<nInsts; inst++) {
-		if ((__InstPtr(self)->i_instvars[inst]) == anObject) {
-		    RETURN (true);
-		}
-	    }
+            for (inst=0; inst<nInsts; inst++) {
+                if ((__InstPtr(self)->i_instvars[inst]) == anObject) {
+                    RETURN (true);
+                }
+            }
 # endif
-	    RETURN (false);
-	}
-
-	/*
-	 * a little optimization: use the fact that all old objects
-	 * refering to a new object are on the remSet; if I am not,
-	 * a trivial reject is possible, if all objects are newbees.
-	 * as a side effect, gather min/max addresses
-	 */
-	if ((__qSpace(self) <= OLDSPACE) && !__isRemembered(self)) {
-	    int allNewBees = 1;
-	    int i;
-
-	    minAddr = (char *)(__arrayVal(aCollection)[0]);
-	    maxAddr = minAddr;
-
-	    for (i=0; i<nObjs; i++) {
-		OBJ anObject = __arrayVal(aCollection)[i];
-
-		if (__isNonNilObject(anObject)) {
-		    int spc = __qSpace(anObject);
-
-		    if ((spc != NEWSPACE) && (spc != SURVSPACE)) {
-			allNewBees = 0;
-		    }
-		}
-
-		if ((char *)anObject < minAddr) {
-		    minAddr = (char *)anObject;
-		} else if ((char *)anObject > maxAddr) {
-		    maxAddr = (char *)anObject;
-		}
-	    }
-	    if (allNewBees) {
-		RETURN (false);
-	    }
-	}
-
-	/*
-	 * fetch min/max in searchList (if not already done above)
-	 */
-	if (minAddr == 0) {
-	    int i;
-
-	    for (i=0; i<nObjs; i++) {
-		char  *anObject = (char *)__arrayVal(aCollection)[i];
-
-		if (anObject < minAddr) {
-		    minAddr = anObject;
-		} else if (anObject > maxAddr) {
-		    maxAddr = anObject;
-		}
-	    }
-	}
-
-	if (((char *)cls >= minAddr) && ((char *)cls <= maxAddr)) {
+            RETURN (false);
+        }
+
+        /*
+         * a little optimization: use the fact that all old objects
+         * refering to a new object are on the remSet; if I am not,
+         * a trivial reject is possible, if all objects are newbees.
+         * as a side effect, gather min/max addresses
+         */
+        if ((__qSpace(self) <= OLDSPACE) && !__isRemembered(self)) {
+            int allNewBees = 1;
+            int i;
+
+            minAddr = (char *)(__arrayVal(aCollection)[0]);
+            maxAddr = minAddr;
+
+            for (i=0; i<nObjs; i++) {
+                OBJ anObject = __arrayVal(aCollection)[i];
+
+                if (__isNonNilObject(anObject)) {
+                    int spc = __qSpace(anObject);
+
+                    if ((spc != NEWSPACE) && (spc != SURVSPACE)) {
+                        allNewBees = 0;
+                    }
+                }
+
+                if ((char *)anObject < minAddr) {
+                    minAddr = (char *)anObject;
+                } else if ((char *)anObject > maxAddr) {
+                    maxAddr = (char *)anObject;
+                }
+            }
+            if (allNewBees) {
+                RETURN (false);
+            }
+        }
+
+        /*
+         * fetch min/max in searchList (if not already done above)
+         */
+        if (minAddr == 0) {
+            int i;
+
+            for (i=0; i<nObjs; i++) {
+                char  *anObject = (char *)__arrayVal(aCollection)[i];
+
+                if (anObject < minAddr) {
+                    minAddr = anObject;
+                } else if (anObject > maxAddr) {
+                    maxAddr = anObject;
+                }
+            }
+        }
+
+        if (((char *)cls >= minAddr) && ((char *)cls <= maxAddr)) {
 # if defined(memsrch4)
-	    if (memsrch4(__arrayVal(aCollection), (INT)cls, nObjs)) {
-		RETURN (true);
-	    }
+            if (memsrch4(__arrayVal(aCollection), (INT)cls, nObjs)) {
+                RETURN (true);
+            }
 # else
-	    int i;
-
-	    for (i=0; i<nObjs; i++) {
-		if (cls == __arrayVal(aCollection)[i]) {
-		    RETURN (true);
-		}
-	    }
+            int i;
+
+            for (i=0; i<nObjs; i++) {
+                if (cls == __arrayVal(aCollection)[i]) {
+                    RETURN (true);
+                }
+            }
 # endif /* memsrch4 */
-	}
-
-	for (inst=0; inst<nInsts; inst++) {
-	    OBJ instVar = __InstPtr(self)->i_instvars[inst];
-	    int i;
-
-	    if (((char *)instVar >= minAddr) && ((char *)instVar <= maxAddr)) {
+        }
+
+        for (inst=0; inst<nInsts; inst++) {
+            OBJ instVar = __InstPtr(self)->i_instvars[inst];
+            int i;
+
+            if (((char *)instVar >= minAddr) && ((char *)instVar <= maxAddr)) {
 # if defined(memsrch4)
-		if (memsrch4(__arrayVal(aCollection), (INT)instVar, nObjs)) {
-		    RETURN (true);
-		}
+                if (memsrch4(__arrayVal(aCollection), (INT)instVar, nObjs)) {
+                    RETURN (true);
+                }
 # else
-		for (i=0; i<nObjs; i++) {
-		    if (instVar == __arrayVal(aCollection)[i]) {
-			RETURN (true);
-		    }
-		}
+                for (i=0; i<nObjs; i++) {
+                    if (instVar == __arrayVal(aCollection)[i]) {
+                        RETURN (true);
+                    }
+                }
 # endif /* memsrch4 */
-	    }
-	}
-	RETURN (false);
+            }
+        }
+        RETURN (false);
     }
 %}.
 
     aCollection do:[:el |
-	(self referencesObject:el) ifTrue:[^ true].
+        (self referencesObject:el) ifTrue:[^ true].
     ].
     ^ false
 !
@@ -8502,19 +8515,19 @@
     "check the instance variables"
     numInst := myClass instSize.
     1 to:numInst do:[:i |
-	((self instVarAt:i) isKindOf:aClass) ifTrue:[^ true]
+        ((self instVarAt:i) isKindOf:aClass) ifTrue:[^ true]
     ].
 
     "check the indexed variables"
     myClass isVariable ifTrue:[
-	myClass isPointers ifFalse:[
-	    "no need to search in non pointer fields"
-	    ((aClass == Number) or:[aClass isSubclassOf:Number]) ifFalse:[^ false].
-	].
-	numInst := self basicSize.
-	1 to:numInst do:[:i |
-	    ((self basicAt:i) isKindOf:aClass) ifTrue:[^ true]
-	]
+        myClass isPointers ifFalse:[
+            "no need to search in non pointer fields"
+            ((aClass == Number) or:[aClass isSubclassOf:Number]) ifFalse:[^ false].
+        ].
+        numInst := self basicSize.
+        1 to:numInst do:[:i |
+            ((self basicAt:i) isKindOf:aClass) ifTrue:[^ true]
+        ]
     ].
     ^ false
 
@@ -8533,21 +8546,21 @@
     "check the instance variables"
     numInst := myClass instSize.
     1 to:numInst do:[:i |
-	inst := self instVarAt:i.
-	(checkBlock value:inst) ifTrue:[actionBlock value:inst].
+        inst := self instVarAt:i.
+        (checkBlock value:inst) ifTrue:[actionBlock value:inst].
     ].
 
     "check the indexed variables"
     myClass isVariable ifTrue:[
-	myClass isPointers ifTrue:[
-	    "no need to search in non pointer fields"
-
-	    numInst := self basicSize.
-	    1 to:numInst do:[:i |
-		inst := self basicAt:i.
-		(checkBlock value:inst) ifTrue:[actionBlock value:inst].
-	    ]
-	]
+        myClass isPointers ifTrue:[
+            "no need to search in non pointer fields"
+
+            numInst := self basicSize.
+            1 to:numInst do:[:i |
+                inst := self basicAt:i.
+                (checkBlock value:inst) ifTrue:[actionBlock value:inst].
+            ]
+        ]
     ].
 
     "
@@ -8571,24 +8584,24 @@
     "check the instance variables"
     numInst := myClass instSize.
     1 to:numInst do:[:i |
-	((self instVarAt:i) isMemberOf:aClass) ifTrue:[^ true]
+        ((self instVarAt:i) isMemberOf:aClass) ifTrue:[^ true]
     ].
 
     "check the indexed variables"
     myClass isVariable ifTrue:[
-	myClass isPointers ifFalse:[
-	    "no need to search in non-pointer indexed fields"
-	    myClass isLongs ifTrue:[
-		(aClass == SmallInteger or:[aClass == LargeInteger]) ifFalse:[^ false].
-	    ] ifFalse:[
-		myClass isFloatsOrDoubles ifTrue:[^ aClass == Float].
-		^ aClass == SmallInteger
-	    ]
-	].
-	numInst := self basicSize.
-	1 to:numInst do:[:i |
-	    ((self basicAt:i) isMemberOf:aClass) ifTrue:[^ true]
-	]
+        myClass isPointers ifFalse:[
+            "no need to search in non-pointer indexed fields"
+            myClass isLongs ifTrue:[
+                (aClass == SmallInteger or:[aClass == LargeInteger]) ifFalse:[^ false].
+            ] ifFalse:[
+                myClass isFloatsOrDoubles ifTrue:[^ aClass == Float].
+                ^ aClass == SmallInteger
+            ]
+        ].
+        numInst := self basicSize.
+        1 to:numInst do:[:i |
+            ((self basicAt:i) isMemberOf:aClass) ifTrue:[^ true]
+        ]
     ].
     ^ false
 
@@ -8608,20 +8621,20 @@
     int nInsts, i;
 
     if (! __isNonNilObject(self)) {
-	RETURN (false);
+        RETURN (false);
     }
     cls = __qClass(self);
     if (cls == anObject) {
-	RETURN (true);
+        RETURN (true);
     }
     flags = __ClassInstPtr(cls)->c_flags;
     if (((INT)flags & __MASKSMALLINT(ARRAYMASK)) == __MASKSMALLINT(POINTERARRAY)) {
-	nInsts = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
+        nInsts = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
     } else {
-	nInsts = __intVal(__ClassInstPtr(cls)->c_ninstvars);
+        nInsts = __intVal(__ClassInstPtr(cls)->c_ninstvars);
     }
     if (! nInsts) {
-	RETURN (false);
+        RETURN (false);
     }
 
 
@@ -8631,24 +8644,24 @@
      * a trivial reject is possible, if anObject is a newbee
      */
     if (__isNonNilObject(anObject)) {
-	if ((__qSpace(self) <= OLDSPACE) && !__isRemembered(self)) {
-	    int spc;
-
-	    if (((spc = __qSpace(anObject)) == NEWSPACE) || (spc == SURVSPACE)) {
-		RETURN (false);
-	    }
-	}
+        if ((__qSpace(self) <= OLDSPACE) && !__isRemembered(self)) {
+            int spc;
+
+            if (((spc = __qSpace(anObject)) == NEWSPACE) || (spc == SURVSPACE)) {
+                RETURN (false);
+            }
+        }
     }
 
 # if defined(memsrch4)
     if (memsrch4(__InstPtr(self)->i_instvars, (INT)anObject, nInsts)) {
-	RETURN (true);
+        RETURN (true);
     }
 # else
     for (i=0; i<nInsts; i++) {
-	if (__InstPtr(self)->i_instvars[i] == anObject) {
-	    RETURN (true);
-	}
+        if (__InstPtr(self)->i_instvars[i] == anObject) {
+            RETURN (true);
+        }
     }
 # endif /* memsrch4 */
 
@@ -8724,8 +8737,8 @@
 
     sema := self synchronizationSemaphore.
     sema notNil ifTrue:[
-	sema wait.              "/ get lock
-	self synchronizationSemaphore:nil.
+        sema wait.              "/ get lock
+        self synchronizationSemaphore:nil.
     ].
 
     "
@@ -8756,10 +8769,10 @@
      subclasses may redefine this method"
 
     aSemaphore isNil ifTrue:[
-	"/ remove Semaphore
-	SynchronizationSemaphores removeKey:self ifAbsent:nil.
+        "/ remove Semaphore
+        SynchronizationSemaphores removeKey:self ifAbsent:nil.
     ] ifFalse:[
-	SynchronizationSemaphores at:self put:aSemaphore.
+        SynchronizationSemaphores at:self put:aSemaphore.
     ].
 
     "Modified: 28.1.1997 / 19:37:48 / stefan"
@@ -8774,8 +8787,8 @@
 
     sema := self synchronizationSemaphore.
     sema isNil ifTrue:[
-	sema := RecursionLock new name:self className.
-	self synchronizationSemaphore:sema.
+        sema := RecursionLock new name:self className.
+        self synchronizationSemaphore:sema.
     ].
 
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
@@ -8810,22 +8823,24 @@
 !
 
 beImmutable
-    "experimental - not yet usable; do not use"
+    "experimental - not yet usable; do not use.
+     For now the #isImmutable flag prohibits only #become*."
 
 %{  /* NOCONTEXT */
     if (! __isNonNilObject(self)) {
-	RETURN (self);
+        RETURN (self);
     }
     __beImmutable(self);
 %}
 !
 
 beMutable
-    "experimental - not yet usable; do not use"
+    "experimental - not yet usable; do not use.
+     For now the #isImmutable flag prohibits only #become*."
 
 %{  /* NOCONTEXT */
     if (! __isNonNilObject(self)) {
-	RETURN (self);
+        RETURN (self);
     }
     __beMutable(self);
 %}
@@ -8849,10 +8864,10 @@
       - the Collection-classes have been rewritten to not use it.)"
 %{
     if (__primBecome(self, anotherObject)) {
-	RETURN ( self );
+        RETURN ( self );
     }
 %}.
-    self primitiveFailed
+    NoModificationError raiseRequestWith:self errorString:' - #become: failed'.
 !
 
 becomeNil
@@ -8865,10 +8880,10 @@
 
 %{
     if (__primBecomeNil(self)) {
-	RETURN ( nil );
+        RETURN ( nil );
     }
 %}.
-    self primitiveFailed
+    NoModificationError raiseRequestWith:self errorString:' - #becomeNil failed'.
 !
 
 becomeSameAs:anotherObject
@@ -8886,10 +8901,10 @@
      or nil, or is a context of a living method (i.e. one that has not already returned)."
 %{
     if (__primBecomeSameAs(self, anotherObject)) {
-	RETURN ( self );
+        RETURN ( self );
     }
 %}.
-    self primitiveFailed
+    NoModificationError raiseRequestWith:self errorString:' - #becomeSameAs: failed'.
 !
 
 changeClassTo:otherClass
@@ -8908,86 +8923,86 @@
 %{
 #ifdef __SCHTEAM__
     ok = (self.isSTInstance() && otherClass.isSTInstance())
-	    ? STObject.True : STObject.False;
+            ? STObject.True : STObject.False;
 #else
     {
-	OBJ other = otherClass;
-
-	if (__isNonNilObject(self)
-	 && __isNonNilObject(other)
-	 && (other != UndefinedObject)
-	 && (other != SmallInteger)) {
-	    ok = true;
-	} else {
-	    ok = false;
-	}
+        OBJ other = otherClass;
+
+        if (__isNonNilObject(self)
+         && __isNonNilObject(other)
+         && (other != UndefinedObject)
+         && (other != SmallInteger)) {
+            ok = true;
+        } else {
+            ok = false;
+        }
     }
 #endif /* not SCHTEAM */
 %}.
     ok == true ifTrue:[
-	ok := false.
-	myClass := self class.
-	myClass == otherClass ifTrue:[
-	    "nothing to change"
-	    ^ self.
-	].
-	myClass flags == otherClass flags ifTrue:[
-	    myClass instSize == otherClass instSize ifTrue:[
-		"same instance layout and types: its ok to do it"
-		ok := true.
-	    ] ifFalse:[
-		myClass isPointers ifTrue:[
-		    myClass isVariable ifTrue:[
-			ok := true
-		    ]
-		]
-	    ]
-	] ifFalse:[
-	    myClass isPointers ifTrue:[
-		"if newClass is a variable class, with instSize <= my instsize,
-		 we can do it (effectively mapping additional instvars into the
-		 variable part) - usefulness is questionable, though"
-
-		otherClass isPointers ifTrue:[
-		    otherClass isVariable ifTrue:[
-			otherClass instSize <= (myClass instSize + self basicSize)
-			ifTrue:[
-			    ok := true
-			]
-		    ] ifFalse:[
-			otherClass instSize == (myClass instSize + self basicSize)
-			ifTrue:[
-			    ok := true
-			]
-		    ]
-		] ifFalse:[
-		    "it does not make sense to convert pointers to bytes ..."
-		]
-	    ] ifFalse:[
-		"does it make sense, to convert bits ?"
-		"could allow byteArray->wordArray->longArray->floatArray->doubleArray here ..."
-		(myClass isBitsExtended and:[otherClass isBitsExtended]) ifTrue:[
-		    ok := true
-		]
-	    ]
-	]
+        ok := false.
+        myClass := self class.
+        myClass == otherClass ifTrue:[
+            "nothing to change"
+            ^ self.
+        ].
+        myClass flags == otherClass flags ifTrue:[
+            myClass instSize == otherClass instSize ifTrue:[
+                "same instance layout and types: its ok to do it"
+                ok := true.
+            ] ifFalse:[
+                myClass isPointers ifTrue:[
+                    myClass isVariable ifTrue:[
+                        ok := true
+                    ]
+                ]
+            ]
+        ] ifFalse:[
+            myClass isPointers ifTrue:[
+                "if newClass is a variable class, with instSize <= my instsize,
+                 we can do it (effectively mapping additional instvars into the
+                 variable part) - usefulness is questionable, though"
+
+                otherClass isPointers ifTrue:[
+                    otherClass isVariable ifTrue:[
+                        otherClass instSize <= (myClass instSize + self basicSize)
+                        ifTrue:[
+                            ok := true
+                        ]
+                    ] ifFalse:[
+                        otherClass instSize == (myClass instSize + self basicSize)
+                        ifTrue:[
+                            ok := true
+                        ]
+                    ]
+                ] ifFalse:[
+                    "it does not make sense to convert pointers to bytes ..."
+                ]
+            ] ifFalse:[
+                "does it make sense, to convert bits ?"
+                "could allow byteArray->wordArray->longArray->floatArray->doubleArray here ..."
+                (myClass isBitsExtended and:[otherClass isBitsExtended]) ifTrue:[
+                    ok := true
+                ]
+            ]
+        ]
     ].
     ok == true ifTrue:[
-	"now, change the receiver's class ..."
+        "now, change the receiver's class ..."
 %{
 #ifdef __SCHTEAM__
-	((STInstance)self).clazz = (STClass)otherClass;
-	return __c__._RETURN(self);
+        ((STInstance)self).clazz = (STClass)otherClass;
+        return __c__._RETURN(self);
 #else
-	{
-	    OBJ me = self;
-
-	    // gcc4.4 does not like this:
-	    // __qClass(me) = otherClass;
-	    __objPtr(me)->o_class = (CLASS_OBJ)otherClass;
-	    __STORE(me, otherClass);
-	    RETURN (me);
-	}
+        {
+            OBJ me = self;
+
+            // gcc4.4 does not like this:
+            // __qClass(me) = otherClass;
+            __objPtr(me)->o_class = (CLASS_OBJ)otherClass;
+            __STORE(me, otherClass);
+            RETURN (me);
+        }
 #endif /* not SCHTEAM */
 %}.
     ].
@@ -9012,14 +9027,16 @@
 !
 
 isImmutable
-    "experimental - not yet usable; do not use"
+    "experimental - not yet usable; do not use.
+     For now the #isImmutable flag prohibits only #become*."
+
 
 %{  /* NOCONTEXT */
     if (! __isNonNilObject(self)) {
-	RETURN (true);
+        RETURN (true);
     }
     if (__isImmutable(self)) {
-	RETURN (true);
+        RETURN (true);
     }
 %}.
     ^ false
@@ -9035,7 +9052,7 @@
     int nInsts, i;
 
     if (! __isNonNilObject(self)) {
-	RETURN (false);
+        RETURN (false);
     }
 
     /*
@@ -9044,34 +9061,34 @@
      * a trivial reject is possible, if anObject is a newbee
      */
     if (__isNonNilObject(anObject)) {
-	if ((__qSpace(self) <= OLDSPACE) && !__isRemembered(self)) {
-	    int spc;
-
-	    if (((spc = __qSpace(anObject)) == NEWSPACE) || (spc == SURVSPACE)) {
-		RETURN (false);
-	    }
-	}
+        if ((__qSpace(self) <= OLDSPACE) && !__isRemembered(self)) {
+            int spc;
+
+            if (((spc = __qSpace(anObject)) == NEWSPACE) || (spc == SURVSPACE)) {
+                RETURN (false);
+            }
+        }
     }
 
     cls = __qClass(self);
 
     flags = __ClassInstPtr(cls)->c_flags;
     if (((INT)flags & __MASKSMALLINT(ARRAYMASK)) == __MASKSMALLINT(POINTERARRAY)) {
-	nInsts = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
+        nInsts = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
     } else {
-	nInsts = __intVal(__ClassInstPtr(cls)->c_ninstvars);
+        nInsts = __intVal(__ClassInstPtr(cls)->c_ninstvars);
     }
     if (! nInsts) {
-	RETURN (false);
+        RETURN (false);
     }
     anyChange = false;
     for (i=0; i<nInsts; i++) {
-	if (__InstPtr(self)->i_instvars[i] == anObject) {
-	    __InstPtr(self)->i_instvars[i] = newRef;
-	    __STORE(self, newRef);
-	    // __dumpObject__(self, __LINE__);
-	    anyChange = true;
-	}
+        if (__InstPtr(self)->i_instvars[i] == anObject) {
+            __InstPtr(self)->i_instvars[i] = newRef;
+            __STORE(self, newRef);
+            // __dumpObject__(self, __LINE__);
+            anyChange = true;
+        }
     }
     RETURN (anyChange);
 %}.
@@ -9098,27 +9115,27 @@
       the receiver is returned here.
 
       Thus, if foo and bar are simple variables or constants,
-	  foo ? bar
+          foo ? bar
       is the same as:
-	  (foo isNil ifTrue:[bar] ifFalse:[foo])
+          (foo isNil ifTrue:[bar] ifFalse:[foo])
 
       if they are message sends, the equivalent code is:
-	  [
-	      |t1 t2|
-
-	      t1 := foo.
-	      t2 := bar.
-	      t1 isNil ifTrue:[t2] ifFalse:[t1]
-	  ] value
+          [
+              |t1 t2|
+
+              t1 := foo.
+              t2 := bar.
+              t1 isNil ifTrue:[t2] ifFalse:[t1]
+          ] value
 
       Can be used to provide defaultValues to variables,
       as in:
-	  foo := arg ? #defaultValue
+          foo := arg ? #defaultValue
 
       Note: this method should never be redefined in classes other than UndefinedObject.
       Notice:
-	 This method is open coded (inlined) by the compiler(s)
-	 - redefining it may not work as expected."
+         This method is open coded (inlined) by the compiler(s)
+         - redefining it may not work as expected."
 
     ^ self
 
@@ -9157,21 +9174,21 @@
       the receiver is returned here.
 
       Thus, if foo and bar are simple variables or constants,
-	  foo ?? bar
+          foo ?? bar
       is the same as:
-	  (foo isNil ifTrue:[bar value] ifFalse:[foo])
+          (foo isNil ifTrue:[bar value] ifFalse:[foo])
 
       if they are message sends, the equivalent code is:
-	  [
-	      |t t2|
-
-	      t := foo.
-	      t isNil ifTrue:[bar value] ifFalse:[t]
-	  ] value
+          [
+              |t t2|
+
+              t := foo.
+              t isNil ifTrue:[bar value] ifFalse:[t]
+          ] value
 
       Can be used to provide defaultValues to variables,
       as in:
-	  foo := arg ?? [ self computeDefault ]
+          foo := arg ?? [ self computeDefault ]
 
       Note: this method should never be redefined in classes other than UndefinedObject.
      "
@@ -9196,8 +9213,8 @@
      This is much like #?, but sends #value to the argument in case of a nil
      receiver.
      Notice:
-	This method is open coded (inlined) by the compiler(s)
-	- redefining it may not work as expected."
+        This method is open coded (inlined) by the compiler(s)
+        - redefining it may not work as expected."
 
     ^ self
 !
@@ -9206,11 +9223,11 @@
     "return the value of the first arg, if I am nil,
      the result from evaluating the 2nd argument, if I am not nil.
      Notice:
-	This method is open coded (inlined) by the compiler(s)
-	- redefining it may not work as expected."
+        This method is open coded (inlined) by the compiler(s)
+        - redefining it may not work as expected."
 
     (notNilBlockOrValue isBlock and:[notNilBlockOrValue argumentCount == 1]) ifTrue:[
-	^ notNilBlockOrValue value:self.
+        ^ notNilBlockOrValue value:self.
     ].
     ^ notNilBlockOrValue value
 !
@@ -9219,11 +9236,11 @@
     "return myself if nil, or the result from evaluating the argument,
      if I am not nil.
      Notice:
-	This method is open coded (inlined) by the compiler(s)
-	- redefining it may not work as expected."
+        This method is open coded (inlined) by the compiler(s)
+        - redefining it may not work as expected."
 
     (aBlockOrValue isBlock and:[aBlockOrValue argumentCount == 1]) ifTrue:[
-	^ aBlockOrValue value:self.
+        ^ aBlockOrValue value:self.
     ].
     ^ aBlockOrValue value
 !
@@ -9232,11 +9249,11 @@
     "return the value of the 2nd arg, if I am nil,
      the result from evaluating the 1st argument, if I am not nil.
      Notice:
-	This method is open coded (inlined) by the compiler(s)
-	- redefining it may not work as expected."
+        This method is open coded (inlined) by the compiler(s)
+        - redefining it may not work as expected."
 
     (notNilBlockOrValue isBlock and:[notNilBlockOrValue argumentCount == 1]) ifTrue:[
-	^ notNilBlockOrValue value:self.
+        ^ notNilBlockOrValue value:self.
     ].
     ^ notNilBlockOrValue value
 !
@@ -9601,21 +9618,21 @@
     "return true if the receiver is an instance of aClass or one of its
      subclasses, false otherwise.
      Advice:
-	use of this to check objects for certain attributes/protocol should
-	be avoided; it limits the reusability of your classes by limiting use
-	to instances of certain classes and fences you into a specific inheritance
-	hierarchy.
-	Use check-methods to check an object for a certain attributes/protocol
-	(such as #isXXXX, #respondsTo: or #isNumber).
-
-	Using #isKindOf: is considered BAD STYLE.
+        use of this to check objects for certain attributes/protocol should
+        be avoided; it limits the reusability of your classes by limiting use
+        to instances of certain classes and fences you into a specific inheritance
+        hierarchy.
+        Use check-methods to check an object for a certain attributes/protocol
+        (such as #isXXXX, #respondsTo: or #isNumber).
+
+        Using #isKindOf: is considered BAD STYLE.
 
      Advice2:
-	Be aware, that using an #isXXX method is usually much faster than
-	using #isKindOf:; because isKindOf: has to walk up all the superclass
-	hierarchy, comparing every class on the way.
-	Due to caching in the VM, a call to #isXXX is normally reached via
-	a single function call.
+        Be aware, that using an #isXXX method is usually much faster than
+        using #isKindOf:; because isKindOf: has to walk up all the superclass
+        hierarchy, comparing every class on the way.
+        Due to caching in the VM, a call to #isXXX is normally reached via
+        a single function call.
      "
 
 %{  /* NOCONTEXT */
@@ -9623,10 +9640,10 @@
 
     thisClass = __Class(self);
     while (thisClass != nil) {
-	if (thisClass == aClass) {
-	    RETURN ( true );
-	}
-	thisClass = __ClassInstPtr(thisClass)->c_superclass;
+        if (thisClass == aClass) {
+            RETURN ( true );
+        }
+        thisClass = __ClassInstPtr(thisClass)->c_superclass;
     }
     RETURN ( false );
 %}
@@ -9687,16 +9704,16 @@
 isMemberOf:aClass
     "return true if the receiver is an instance of aClass, false otherwise.
      Advice:
-	use of this to check objects for certain attributes/protocol should
-	be avoided; it limits the reusability of your classes by limiting use
-	to instances of a certain class.
-	Use check-methods to check an object for a certain attributes/protocol
-	(such as #isXXX, #respondsTo: or #isNumber);
-
-	Using #isMemberOf: is considered BAD STYLE.
+        use of this to check objects for certain attributes/protocol should
+        be avoided; it limits the reusability of your classes by limiting use
+        to instances of a certain class.
+        Use check-methods to check an object for a certain attributes/protocol
+        (such as #isXXX, #respondsTo: or #isNumber);
+
+        Using #isMemberOf: is considered BAD STYLE.
      Notice:
-	This method is open coded (inlined) by the compiler(s)
-	- redefining it may not work as expected."
+        This method is open coded (inlined) by the compiler(s)
+        - redefining it may not work as expected."
 
     ^ (self class) == aClass
 !
@@ -9754,8 +9771,8 @@
      Because isNil is redefined in UndefinedObject,
      the receiver is definitely not nil here, so unconditionally return false.
      Notice:
-	This method is open coded (inlined) by the compiler(s)
-	- redefining it may not work as expected."
+        This method is open coded (inlined) by the compiler(s)
+        - redefining it may not work as expected."
 
     ^ false
 !
@@ -9778,11 +9795,11 @@
     ^ false
 
     "
-	21 isNonByteCollection
-	'abc' isNonByteCollection
-	#'abc' isNonByteCollection
-	#[1 2 3] isNonByteCollection
-	#(1 2 3) isNonByteCollection
+        21 isNonByteCollection
+        'abc' isNonByteCollection
+        #'abc' isNonByteCollection
+        #[1 2 3] isNonByteCollection
+        #(1 2 3) isNonByteCollection
     "
 !
 
@@ -9957,6 +9974,12 @@
     ^ false
 !
 
+isStructure
+    "redefined in Structure>>#doesNotUnderstand"
+
+    ^ false
+!
+
 isSymbol
     "return true if the receiver is some kind of symbol;
      false is returned here - the method is only redefined in Symbol."
@@ -10068,8 +10091,8 @@
      Because notNil is redefined in UndefinedObject,
      the receiver is definitely not nil here, so unconditionally return true.
      Notice:
-	This method is open coded (inlined) by the compiler(s)
-	- redefining it may not work as expected."
+        This method is open coded (inlined) by the compiler(s)
+        - redefining it may not work as expected."
 
     ^ true
 ! !
@@ -10098,7 +10121,7 @@
      It could also be put into some logfile or printed on the standard output/error."
 
     ActivityNotification isHandled ifTrue:[
-	^ ActivityNotification raiseRequestWith:self errorString:aString
+        ^ ActivityNotification raiseRequestWith:self errorString:aString
     ].
 
     "
@@ -10108,12 +10131,12 @@
 
     "
      ActivityNotification handle:[:ex |
-	ex errorString printCR.
-	ex proceed.
+        ex errorString printCR.
+        ex proceed.
      ] do:[
-	'hello' printCR.
-	self activityNotification:'doing some long time computation'.
-	'world' printCR.
+        'hello' printCR.
+        self activityNotification:'doing some long time computation'.
+        'world' printCR.
      ]
     "
 
@@ -10145,7 +10168,7 @@
 
     answer := self confirmWithCancel:aString.
     answer isNil ifTrue:[
-	^ cancelBlock value
+        ^ cancelBlock value
     ].
     ^ answer
 
@@ -10181,10 +10204,10 @@
      by handling the UserConfirmation."
 
     ^ UserConfirmation new
-	defaultAnswer:defaultAnswerOrNil;
-	canCancel:true;
-	errorString:aString;
-	raiseRequest
+        defaultAnswer:defaultAnswerOrNil;
+        canCancel:true;
+        errorString:aString;
+        raiseRequest
 
     "
      nil confirmWithCancel:'hello' defaultAnswer:true
@@ -10197,10 +10220,10 @@
      and give user a chance to enter debugger."
 
     ^ self
-	errorNotify:aString
-	from:thisContext sender
-	allowDebug:true
-	mayProceed:true
+        errorNotify:aString
+        from:thisContext sender
+        allowDebug:true
+        mayProceed:true
 
     "
      nil errorNotify:'hello there'
@@ -10233,141 +10256,141 @@
     |currentScreen con sender action boxLabels boxValues default s|
 
     Smalltalk isInitialized ifFalse:[
-	'errorNotification: ' print. aString printCR.
-	con := aContext ? thisContext methodHome.
-	con sender printAllLevels:10.
-	^ nil
+        'errorNotification: ' print. aString printCR.
+        con := aContext ? thisContext methodHome.
+        con sender printAllLevels:10.
+        ^ nil
     ].
 
     (Dialog isNil
      or:[Screen isNil
      or:[(currentScreen := Screen current) isNil
      or:[currentScreen isOpen not]]]) ifTrue:[
-	"
-	 on systems without GUI, simply show
-	 the message on the Transcript and abort.
-	"
-	Transcript showCR:aString.
-	AbortOperationRequest raise.
-	"not reached"
-	^ nil
+        "
+         on systems without GUI, simply show
+         the message on the Transcript and abort.
+        "
+        Transcript showCR:aString.
+        AbortOperationRequest raise.
+        "not reached"
+        ^ nil
     ].
 
     Processor activeProcessIsSystemProcess ifTrue:[
-	action := #debug.
-	sender := aContext.
-	Debugger isNil ifTrue:[
-	    '****************** Caught Error while in SystemProcess ****************' errorPrintCR.
-	    aString errorPrintCR.
-	    Exception handle:[:ex |
-		'Caught recursive error while printing backtrace:' errorPrintCR.
-		ex description errorPrintCR.
-	    ] do:[
-		thisContext fullPrintAll.
-	    ].
-	    action := #abort.
-	].
+        action := #debug.
+        sender := aContext.
+        Debugger isNil ifTrue:[
+            '****************** Caught Error while in SystemProcess ****************' errorPrintCR.
+            aString errorPrintCR.
+            Exception handle:[:ex |
+                'Caught recursive error while printing backtrace:' errorPrintCR.
+                ex description errorPrintCR.
+            ] do:[
+                thisContext fullPrintAll.
+            ].
+            action := #abort.
+        ].
     ] ifFalse:[
-	Dialog autoload.        "in case it is autoloaded"
-
-	Error handle:[:ex |
-	    "/ a recursive error - quickly enter debugger
-	    "/ this happened, when I corrupted the Dialog class ...
-	    ('Object [error]: ' , ex description , ' caught in errorNotification') errorPrintCR.
-	    action := #debug.
-	    ex return.
-	] do:[ |s|
-	    sender := aContext.
-	    sender isNil ifTrue:[
-		sender := thisContext methodHome sender.
-	    ].
-	    con := sender.
-
-	    "/ skip intermediate (signal & exception) contexts
-	    DebugView notNil ifTrue:[
-		con := DebugView interestingContextFrom:sender
-	    ].
-
-	    "/ show the first few contexts
-
-	    s := CharacterWriteStream with:aString.
-	    s cr; cr.
-	    s nextPutLine:'Calling Chain:'.
-	    s nextPutLine:'--------------------------------------------------------------'.
-	    1 to:25 do:[:n |
-		con notNil ifTrue:[
-		    con printOn:s.
-		    s cr.
-		    con := con sender
-		]
-	    ].
-
-	    mayProceed ifTrue:[
-		boxLabels := #('Proceed').
-		boxValues := #(#proceed).
-		default := #proceed.
-	    ] ifFalse:[
-		boxLabels := #().
-		boxValues := #().
-	    ].
-
-	    AbortOperationRequest isHandled ifTrue:[
-		default := #abort.
-		boxLabels := boxLabels , #('Abort').
-		boxValues := boxValues , #(#abort).
-		AbortAllOperationRequest isHandled ifTrue:[
-		    boxLabels := boxLabels , #('Abort All').
-		    boxValues := boxValues , #(#abortAll).
-		].
-		true "allowDebug" ifTrue:[
-		    boxLabels := boxLabels , #('Copy Trace and Abort').
-		    boxValues := boxValues , #(#copyAndAbort).
-		].
-	    ] ifFalse:[
-		mayProceed "and:[allowDebug]" ifTrue:[
-		    boxLabels := boxLabels , #('Copy Trace and Proceed').
-		    boxValues := boxValues , #(#copyAndProceed).
-		].
-	    ].
-
-	    (allowDebug and:[Debugger notNil]) ifTrue:[
-		boxLabels := boxLabels , #('Debug').
-		boxValues := boxValues , #(#debug).
-		default := #debug.
-	    ].
-
-	    action := Dialog
-		    choose:s contents
-		    label:('Exception [' , Processor activeProcess nameOrId , ']')
-		    image:WarningBox errorIconBitmap
-		    labels:boxLabels
-		    values:boxValues
-		    default:default
-		    onCancel:nil.
-	].
+        Dialog autoload.        "in case it is autoloaded"
+
+        Error handle:[:ex |
+            "/ a recursive error - quickly enter debugger
+            "/ this happened, when I corrupted the Dialog class ...
+            ('Object [error]: ' , ex description , ' caught in errorNotification') errorPrintCR.
+            action := #debug.
+            ex return.
+        ] do:[ |s|
+            sender := aContext.
+            sender isNil ifTrue:[
+                sender := thisContext methodHome sender.
+            ].
+            con := sender.
+
+            "/ skip intermediate (signal & exception) contexts
+            DebugView notNil ifTrue:[
+                con := DebugView interestingContextFrom:sender
+            ].
+
+            "/ show the first few contexts
+
+            s := CharacterWriteStream with:aString.
+            s cr; cr.
+            s nextPutLine:'Calling Chain:'.
+            s nextPutLine:'--------------------------------------------------------------'.
+            1 to:25 do:[:n |
+                con notNil ifTrue:[
+                    con printOn:s.
+                    s cr.
+                    con := con sender
+                ]
+            ].
+
+            mayProceed ifTrue:[
+                boxLabels := #('Proceed').
+                boxValues := #(#proceed).
+                default := #proceed.
+            ] ifFalse:[
+                boxLabels := #().
+                boxValues := #().
+            ].
+
+            AbortOperationRequest isHandled ifTrue:[
+                default := #abort.
+                boxLabels := boxLabels , #('Abort').
+                boxValues := boxValues , #(#abort).
+                AbortAllOperationRequest isHandled ifTrue:[
+                    boxLabels := boxLabels , #('Abort All').
+                    boxValues := boxValues , #(#abortAll).
+                ].
+                true "allowDebug" ifTrue:[
+                    boxLabels := boxLabels , #('Copy Trace and Abort').
+                    boxValues := boxValues , #(#copyAndAbort).
+                ].
+            ] ifFalse:[
+                mayProceed "and:[allowDebug]" ifTrue:[
+                    boxLabels := boxLabels , #('Copy Trace and Proceed').
+                    boxValues := boxValues , #(#copyAndProceed).
+                ].
+            ].
+
+            (allowDebug and:[Debugger notNil]) ifTrue:[
+                boxLabels := boxLabels , #('Debug').
+                boxValues := boxValues , #(#debug).
+                default := #debug.
+            ].
+
+            action := Dialog
+                    choose:s contents
+                    label:('Exception [' , Processor activeProcess nameOrId , ']')
+                    image:WarningBox errorIconBitmap
+                    labels:boxLabels
+                    values:boxValues
+                    default:default
+                    onCancel:nil.
+        ].
     ].
 
     action == #debug ifTrue:[
-	^ Debugger enter:sender withMessage:aString mayProceed:mayProceed
+        ^ Debugger enter:sender withMessage:aString mayProceed:mayProceed
     ].
     action == #proceed ifTrue:[
-	^ nil.
+        ^ nil.
     ].
     (action == #copyAndProceed
     or:[action == #copyAndAbort]) ifTrue:[
-	s := '' writeStream.
-	Exception handle:[:ex |
-	    'Caught recursive error while printing backtrace' errorPrintCR.
-	] do:[
-	    sender fullPrintAllOn:s.
-	].
-	currentScreen rootView setClipboardText:s contents.
-	action == #copyAndProceed ifTrue:[
-	    ^ nil
-	].
+        s := '' writeStream.
+        Exception handle:[:ex |
+            'Caught recursive error while printing backtrace' errorPrintCR.
+        ] do:[
+            sender fullPrintAllOn:s.
+        ].
+        currentScreen rootView setClipboardText:s contents.
+        action == #copyAndProceed ifTrue:[
+            ^ nil
+        ].
     ].
     (action == #abortAll) ifTrue:[
-	AbortAllOperationRequest raise
+        AbortAllOperationRequest raise
     ].
 
     AbortOperationRequest raise.
@@ -10400,12 +10423,12 @@
 
     "
      InformationSignal handle:[:ex |
-	'no box popped' printCR.
-	ex proceed.
+        'no box popped' printCR.
+        ex proceed.
      ] do:[
-	'hello' printCR.
-	self information:'some info'.
-	'world' printCR.
+        'hello' printCR.
+        self information:'some info'.
+        'world' printCR.
      ]
     "
 
@@ -10420,9 +10443,9 @@
 
 
     Smalltalk isInitialized ifFalse:[
-	"/ thisContext fullPrintAll.
-	'information: ' print. aString printCR.
-	^ self
+        "/ thisContext fullPrintAll.
+        'information: ' print. aString printCR.
+        ^ self
     ].
     UserNotification raiseRequestWith:self errorString:aString.
 
@@ -10450,12 +10473,12 @@
 
     "
      Warning handle:[:ex |
-	Transcript showCR:ex description.
-	ex proceed.
+        Transcript showCR:ex description.
+        ex proceed.
      ] do:[
-	'hello' printCR.
-	self warn:'some info'.
-	'world' printCR.
+        'hello' printCR.
+        self warn:'some info'.
+        'world' printCR.
      ]
     "
 
@@ -10479,7 +10502,6 @@
 
 
 
-
 !Object class methodsFor:'documentation'!
 
 version
@@ -10493,11 +10515,6 @@
 version_HG
 
     ^ '$Changeset: <not expanded> $'
-!
-
-version_SVN
-    ^ '$ Id: Object.st 10643 2011-06-08 21:53:07Z vranyj1  $'
 ! !
 
-
 Object initialize!
--- a/PCFilename.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/PCFilename.st	Sun Oct 09 21:28:18 2016 +0100
@@ -594,14 +594,30 @@
     "return true, if such a file exists and is an executable program.
      (i.e. for directories, false is returned.)"
 
-    |mySuffix|
+    |osName|
 
-    mySuffix := self suffix asLowercase.
-    (OperatingSystem executableFileExtensions includes: mySuffix) ifTrue:[
-	^ super isExecutableProgram
+    osName := self osNameForAccess.
+    (OperatingSystem getBinaryType:osName) notNil ifTrue:[
+        ^ true.
+    ].
+
+    (self suffix asLowercase = 'bat') ifTrue:[
+        ^ (OperatingSystem isValidPath:osName)      
+            and:[(OperatingSystem isDirectory:osName) not].
     ].
     ^ false
 
+    "
+        '%windir%\notepad.exe' asFilename isExecutableProgram
+        '%windir%\notepad' asFilename isExecutableProgram
+        '%windir%\system32\kernel32.dll' asFilename isExecutableProgram
+        'bmake.bat' asFilename isExecutableProgram
+        'c:\' asFilename isExecutableProgram
+        OperatingSystem getBinaryType:'bmake.bat'  
+        OperatingSystem getBinaryType:'c:\'  
+    "
+
+
     "Created: / 16-10-1997 / 13:19:10 / cg"
     "Modified: / 09-09-1998 / 20:17:52 / cg"
     "Modified: / 23-08-2011 / 21:24:57 / jv"
--- a/ProjectDefinition.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/ProjectDefinition.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2006 by eXept Software AG
               All Rights Reserved
@@ -17,9 +15,9 @@
 
 Object subclass:#ProjectDefinition
 	instanceVariableNames:''
-	classVariableNames:'LibraryType GUIApplicationType NonGUIApplicationType
-		PackagesBeingLoaded Verbose AbbrevDictionary AccessLock
-		FolderForSubApplicationsType'
+	classVariableNames:'AbbrevDictionary AccessLock FolderForSubApplicationsType
+		GUIApplicationType LibraryType NonGUIApplicationType
+		PackagesBeingLoaded Verbose'
 	poolDictionaries:''
 	category:'System-Support-Projects'
 !
@@ -1858,6 +1856,7 @@
     |preRequisites|
 
     preRequisites := self searchForPreRequisites first.
+    preRequisites removeAllKeys:self excludedFromMandatoryPreRequisites ifAbsent:[].
     preRequisites removeAllKeys:self excludedFromPreRequisites ifAbsent:[].
 
     ^ String streamContents:[:s |
@@ -1870,7 +1869,7 @@
 
             s spaces:8.
             eachPackageID asSymbol storeOn:s.
-            reason := preRequisites at:eachPackageID ifAbsent:nil.
+            reason := preRequisites at:eachPackageID ifAbsent:[nil].
             reason notEmptyOrNil ifTrue:[
                 s nextPutAll:'    "'; nextPutAll:reason anElement; nextPut:$".
             ].
@@ -1945,6 +1944,7 @@
     preRequisites := preRequisitesColl second.
     preRequisites
         removeAllKeys:self excludedFromPreRequisites ifAbsent:[];
+        removeAllKeys:self excludedFromRequiredPreRequisites ifAbsent:[];
         removeAllKeys:preRequisitesColl first keys ifAbsent:[].  "remove the mandatory prerequisites"
 
     ^ String streamContents:[:s |
@@ -1957,7 +1957,7 @@
 
             s spaces:8.
             eachPackageID asSymbol storeOn:s.
-            reason := preRequisites at:eachPackageID ifAbsent:nil.
+            reason := preRequisites at:eachPackageID ifAbsent:[nil].
             reason notEmptyOrNil ifTrue:[
                 s nextPutAll:'    "'; nextPutAll:reason anElement; nextPut:$".
             ].
@@ -2103,9 +2103,32 @@
 
 !ProjectDefinition class methodsFor:'description'!
 
-excludedFromPreRequisites
+excludedFromMandatoryPreRequisites
     "list packages which are to be explicitely excluded from the automatic constructed
-     prerequisites list. If empty, everything that is found along the inheritance of any of
+     mandatory prerequisites list. 
+     If empty, everything that is found along the inheritance of any of
+     my classes is considered to be a prerequisite package."
+
+    ^ #()
+!
+
+excludedFromPreRequisites
+    "obsolete; temporarily, this is still called for, but will eventually vanish.
+    
+     List packages which are to be explicitely excluded from the automatic constructed
+     prerequisites lists (both). 
+     If empty, everything that is found along the inheritance of any of
+     my classes is considered to be a prerequisite package."
+
+    ^ #()
+
+    "Modified: / 17-08-2006 / 19:48:59 / cg"
+!
+
+excludedFromRequiredPreRequisites
+    "list packages which are to be explicitely excluded from the automatic constructed
+     required prerequisites list. 
+     If empty, everything that is found along the inheritance of any of
      my classes is considered to be a prerequisite package."
 
     ^ #()
@@ -2154,7 +2177,8 @@
 !
 
 preRequisites
-    "list packages which are required as a prerequisite."
+    "list packages which are required as a prerequisite (both mandatory and referenced).
+     This is used to build dependency chains in makefiles"
 
     "use an OrderedSet here, so that mandatory prerequisites come first"
 
@@ -2788,7 +2812,8 @@
 
 companyName
     "Returns a company string which will appear in <lib>.rc.
-     Under win32, this is placed into the dlls file-info"
+     Under win32, this is placed into the dll's file-info.
+     Other systems may put it elsewhere, or ignore it."
 
     (
       #(
@@ -2942,7 +2967,8 @@
 
 legalCopyright
     "Returns a copyright string which will appear in <lib>.rc.
-     Under win32, this is placed into the dlls file-info"
+     Under win32, this is placed into the dll's file-info.
+     Other systems may put it elsewhere, or ignore it."
 
     self module = 'stx' ifTrue:[
         "hardwired-default"
@@ -3009,13 +3035,16 @@
 !
 
 productFilename
-    "Returns a filename which be used as linkname, product file name etc."
+    "Returns a filename which will be used as linkname, product file name etc.
+     The final deployable will be named like this (<fn>.dmg / <fn>Setup.ex / <fn>Install.pkg etc.)"
 
     ^ self productNameAsValidFilename
 
     "
      stx_projects_smalltalk productName
      stx_projects_smalltalk productFilename
+     stx_libbasic productFilename
+     stx_doc_coding_demoConsoleApp productFilename
     "
 
     "Created: / 01-03-2007 / 19:33:06 / cg"
@@ -3061,7 +3090,7 @@
 
 productName
     "Returns a product name which will appear in <lib>.rc.
-     Under win32, this is placed into the dlls file-info.
+     Under win32, this is placed into the dll's file-info.
      This method is usually redefined in a concrete application definition"
 
     |m nm|
@@ -3098,16 +3127,18 @@
 !
 
 productNameAsValidFilename
-    "Returns a product name which will appear in <lib>.rc.
-     Under win32, this is placed into the dlls file-info"
+    "Returns a filename generated from the product name.
+     This will be the name of the deployable package (i.e. <fn>.dmg, <fn>Setup.exe, etc.)"
 
     |nm|
 
     nm := self productName.
-    ^ nm copy replaceAny:'/\:;.,' with:$_
+    ^ nm copy replaceAny:'/\:;., ' with:$_
 
     "
      'Smalltalk/X' replaceAny:'/\:;.,' with:nil
+     stx_doc_coding_demoConsoleApp productName
+     stx_doc_coding_demoConsoleApp productNameAsValidFilename
     "
 
     "Created: / 01-03-2007 / 19:19:21 / cg"
@@ -3814,6 +3845,7 @@
         at: 'TOP' put: (self pathToTopWithSeparator:'/');                 "/ unix here
 "/        at: 'MODULE_PATH' put: ( self moduleDirectory );        "/ unix here
         at: 'DESCRIPTION' put: (self description);
+        at: 'PRODUCT_NAME' put: (self productName);
         at: 'PRODUCT_VERSION' put: (self productVersion);
         at: 'PRODUCT_DATE' put: (self productDate);
         at: 'PRODUCT_PUBLISHER' put: (self productPublisher);
@@ -3822,8 +3854,13 @@
         at: 'PRODUCT_TYPE' put: (self productType);
         at: 'PRODUCT_LICENSE' put: (self productLicense);
         at: 'PRODUCT_DESCRIPTION' put: (self productDescription);
+        at: 'PRODUCT_CPU_VERSIONS' put: 'x86';
+        at: 'PRODUCT_ROOT_NAME' put: (self productName);
         at: 'MAINTAINER' put: (self productMaintainer);
         at: 'PACKAGER' put: (self productPublisher);
+        at: 'ADDITIONAL_SOURCE_DIRS' put: '';
+        at: 'ADDITIONAL_COPYFILES' put: '';
+        at: 'ADDITIONAL_INSTALL' put: '';
         yourself.
 
 
@@ -4862,12 +4899,12 @@
 ShortName: %(APPLICATION)
 SoftwareVersion: %(PRODUCT_VERSION)
 DisplayName: %(DESCRIPTION)
-RootName: @exept.de/expecco:$SOFTWAREVERSION
+RootName: %(PRODUCT_ROOT_NAME)
 Summary: %(DESCRIPTION)
 Maintainer: %(MAINTAINER)
 Packager: %(PACKAGER)
 PackageVersion: 1
-CPUArchitectures: x86
+CPUArchitectures: %(PRODUCT_CPU_VERSIONS)
 AutopackageTarget: 1.0
 Type: %(PRODUCT_TYPE)
 License: %(PRODUCT_LICENSE)
@@ -4898,18 +4935,7 @@
 [Imports]
 import <<EOF
 $source_dir/%(APPLICATION)
-$source_dir/resources
-$source_dir/keyboard.rc
-$source_dir/keyboardMacros.rc
-$source_dir/display.rc
-$source_dir/host.rc
-$source_dir/../doc
-$source_dir/../testsuites/webedition
-$source_dir/../projects/libraries
-$source_dir/../reportGenerator/tools
-$source_dir/../../pdf/afm
-$source_dir/../plugin/selenium/libexept_expecco_plugin_selenium.so
-$source_dir/../externalTools
+%(ADDITIONAL_SOURCE_DIRS)
 EOF
 
 for i in $source_dir/*.so
@@ -4925,22 +4951,12 @@
 
 find . -type d \( -name CVS -or -name ''not_*'' \) -print | xargs rm -rf
 mkdir -p $MYPREFIX
-copyFiles expecco *.rc resources        $MYPREFIX/bin
-copyFiles *.so                          $MYPREFIX/lib
-copyFiles doc externalTools             $MYPREFIX/packages/exept/expecco
-copyFiles webedition/projects libraries $MYPREFIX/testsuites
-copyFiles tools                         $MYPREFIX/packages/exept/expecco/reportGenerator
-copyFiles afm                           $MYPREFIX/packages/exept/pdf
-copyFiles libexept_expecco_plugin_selenium.so   $MYPREFIX/plugin
-
-#installExe expecco
+copyFiles %(PRODUCT_NAME) *.rc resources        $MYPREFIX/bin
+%(ADDITIONAL_COPYFILES)
+
+#installExe %(PRODUCT_NAME)
 #installLib *.so
-#installData resources
-#installData keyboard.rc
-#installData keyboardMacros.rc
-#installData host.rc
-#installData display.rc
-#installData doc
+%(ADDITIONAL_INSTALL)
 
 [Uninstall]
 # Leaving this at the default is safe unless you use custom commands in
@@ -7227,6 +7243,7 @@
         ^ OrderedSet new
             addAll:self mandatoryPreRequisites;
             "/ addAll:self includedInPreRequisites;
+            removeAllFoundIn:self excludedFromMandatoryPreRequisites;
             removeAllFoundIn:self excludedFromPreRequisites;
             yourself.
     ].
@@ -7235,6 +7252,7 @@
     ^ Set new
         addAll:self preRequisites;
         addAll:self includedInPreRequisites;
+        removeAllFoundIn:self excludedFromMandatoryPreRequisites;
         removeAllFoundIn:self excludedFromPreRequisites;
         remove:self package ifAbsent:[];
         yourself.
@@ -7244,8 +7262,7 @@
     "get the preRequisites, that are not excluded.
      This method appears to be obsolete, because its functionality
      is now included in #preRequisites.
-     But is to be kept for backward compatibilty with old
-     existing subclasses."
+     But is to be kept for backward compatibilty with old existing subclasses."
 
     self mandatoryPreRequisites notEmpty ifTrue:[
         "this is a new subclass - avoid overhead"
--- a/Smalltalk.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/Smalltalk.st	Sun Oct 09 21:28:18 2016 +0100
@@ -2018,18 +2018,21 @@
 
     already := IdentitySet new:NumberOfClassesHint*2.
     self allClassesDo:[:eachClass |
-	|cls|
-
-	cls := eachClass theNonMetaclass.
-	(already includes:cls) ifFalse:[
-	    aBlock value:cls.
-	    already add:cls.
-	].
-	cls := cls class.
-	(already includes:cls) ifFalse:[
-	    aBlock value:cls.
-	    already add:cls.
-	].
+        |cls|
+
+        cls := eachClass theNonMetaclass.
+        (already includes:cls) ifFalse:[
+            aBlock value:cls.
+            already add:cls.
+        ].
+        cls := cls class.
+        (already includes:cls) ifFalse:[
+            aBlock value:cls.
+            already add:cls.
+        ].
+        already size > (NumberOfClassesHint * 2) ifTrue:[
+            NumberOfClassesHint := (already size // 2) + 1
+        ].    
     ].
 !
 
@@ -4840,6 +4843,7 @@
         self exit:statusInteger
     ] ifFalse:[
         self warn:'Application asks Smalltalk to exit (suppressed in IDE).'.
+        AbortOperationRequest raise.
     ]
 
     "
--- a/StandaloneStartup.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/StandaloneStartup.st	Sun Oct 09 21:28:18 2016 +0100
@@ -509,7 +509,8 @@
 checkForAndExitIfAnotherApplicationInstanceIsRunning
     "if another instance of this application is running,
      send it an openFile command for my file-argument, and exit.
-     (i.e. to let the already running application open up another window)."
+     (i.e. the already running app gets a (processOpenPathCommand:argument) message
+      to ask it to open up another window)."
 
     |shouldExit|
 
@@ -598,7 +599,7 @@
 processStartupOfASecondInstance
     "This is executed when I have been started as a second instance of an already running application.
      If I can get the currentID (i.e. windowID) of the first one and there is a command line argument with a file, 
-     send a message to the main window of the already running application, to ask it for another window.
+     send a message (processOpenPathCommand:argument) to the main window of the already running application, to ask it for another window.
      If the currentID is unknown, ask if the user wants to open a new instance of the application anyway.
      Return true if the first instance has been notified, and this second instance should exit."
 
@@ -1156,6 +1157,13 @@
 
     "Created: / 19-09-2006 / 16:37:55 / cg"
     "Modified: / 24-05-2011 / 17:23:18 / cg"
+!
+
+usageAndExitWith:exitCode
+    "show the usage message, then exit with given exitCode"
+    
+    self usage.
+    Smalltalk exitIfStandalone:exitCode
 ! !
 
 !StandaloneStartup class methodsFor:'startup-to be redefined'!
--- a/String.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/String.st	Sun Oct 09 21:28:18 2016 +0100
@@ -520,7 +520,6 @@
 
 
 
-
 !String class methodsFor:'queries'!
 
 defaultPlatformClass
@@ -545,6 +544,7 @@
 
 
 
+
 !String methodsFor:'accessing'!
 
 at:index
@@ -2693,6 +2693,7 @@
 beImmutable
     "make myself write-protected"
 
+    super beImmutable.
     self changeClassTo:ImmutableString
 !
 
--- a/SystemChangeNotifier.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/SystemChangeNotifier.st	Sun Oct 09 21:28:18 2016 +0100
@@ -1,5 +1,9 @@
+"{ Encoding: utf8 }"
+
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#SystemChangeNotifier
 	instanceVariableNames:'silenceLevel'
 	classVariableNames:'UniqueInstance'
@@ -81,6 +85,10 @@
     "dummy for now "
 !
 
+notify:aStakeHolder ofAllSystemChangesUsing:changeMessage
+    "dummy for now "
+!
+
 notify:aStakeHolder ofSystemChangesOfItem:anItemSymbol change: changeTypeSymbol using: changeMessage
     "dummy for now "
 ! !
@@ -88,6 +96,6 @@
 !SystemChangeNotifier class methodsFor:'documentation'!
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/SystemChangeNotifier.st,v 1.6 2013-06-23 22:23:09 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/Win32OperatingSystem.st	Mon Oct 03 12:44:41 2016 +0100
+++ b/Win32OperatingSystem.st	Sun Oct 09 21:28:18 2016 +0100
@@ -3,7 +3,7 @@
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
  COPYRIGHT (c) 1998-2004 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -574,19 +574,19 @@
     int i, len;
 
     if (__isStringLike(string)) {
-        len = __stringSize(string);
-        if (len > bufferSize) len = bufferSize;
-        for (i=0; i<len; i++) {
-            buffer[i] = __stringVal(string)[i];
-        }
+	len = __stringSize(string);
+	if (len > bufferSize) len = bufferSize;
+	for (i=0; i<len; i++) {
+	    buffer[i] = __stringVal(string)[i];
+	}
     } else if (__isUnicode16String(string)) {
-        len = __unicode16StringSize(string);
-        if (len > bufferSize) len = bufferSize;
-        for (i=0; i<len; i++) {
-            buffer[i] = __unicode16StringVal(string)[i];
-        }
+	len = __unicode16StringSize(string);
+	if (len > bufferSize) len = bufferSize;
+	for (i=0; i<len; i++) {
+	    buffer[i] = __unicode16StringVal(string)[i];
+	}
     } else {
-        return(-1);
+	return(-1);
     }
     buffer[len] = 0;
     return(len);
@@ -609,43 +609,43 @@
     tv.tv_usec = 0;
 
     if (readMode) {
-        n = select (1 , &fds, NULL, NULL, &tv);  // first parameter to select is ignored in windows
+	n = select (1 , &fds, NULL, NULL, &tv);  // first parameter to select is ignored in windows
     } else {
-        n = select (1, NULL, &fds, NULL, &tv);
+	n = select (1, NULL, &fds, NULL, &tv);
     }
 
     if (n == 0) {
-        return (0);
+	return (0);
     }
 
     if (n > 0) {
-        return (FD_ISSET(handle, &fds) ? 1 : 0);
+	return (FD_ISSET(handle, &fds) ? 1 : 0);
     }
 
     winErrNo = WSAGetLastError();
     switch (winErrNo) {
-        case WSAENOTSOCK:
-            if (readMode) {
-                DWORD  w = 0;
-
-                if (PeekNamedPipe (handle, 0, 0, 0, & w, 0)) {
-                    return (w > 0);
-                }
+	case WSAENOTSOCK:
+	    if (readMode) {
+		DWORD  w = 0;
+
+		if (PeekNamedPipe (handle, 0, 0, 0, & w, 0)) {
+		    return (w > 0);
+		}
 #if 0
-                console_fprintf(stderr, "_canAccessIOWithoutBlocking non Socket\n");
-#endif
-                return (-1);
-            }
-            /* in writeMode we return always 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 always 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 */
@@ -667,7 +667,7 @@
     FARPROC entry;
 
     if (*pLibHandle == NULL) {
-        *pLibHandle = LoadLibrary(libraryName);
+	*pLibHandle = LoadLibrary(libraryName);
     }
     entry = GetProcAddress(*pLibHandle, functionName);
     return entry;
@@ -728,11 +728,11 @@
     return(__MKINT(lTime));
 #else
     if (lTime >= (LONGLONG)11644473600000L) {
-        lTime -= (LONGLONG)11644473600000L;  // the number of millis from 1.1.1601 to 1.1.1970
-        return(__MKLARGEINT64(1, (unsigned INT)(lTime & 0xFFFFFFFF), (unsigned INT)(lTime >> 32)));
+	lTime -= (LONGLONG)11644473600000L;  // the number of millis from 1.1.1601 to 1.1.1970
+	return(__MKLARGEINT64(1, (unsigned INT)(lTime & 0xFFFFFFFF), (unsigned INT)(lTime >> 32)));
     } else {
-        lTime = (LONGLONG)11644473600000L - lTime;
-        return(__MKLARGEINT64(-1, (unsigned INT)(lTime & 0xFFFFFFFF), (unsigned INT)(lTime >> 32)));
+	lTime = (LONGLONG)11644473600000L - lTime;
+	return(__MKLARGEINT64(-1, (unsigned INT)(lTime & 0xFFFFFFFF), (unsigned INT)(lTime >> 32)));
     }
 #endif
 }
@@ -746,7 +746,7 @@
     UINT hi = __unsignedLongIntVal(tHigh);
 
     if (hi == 0 && !__isSmallInteger(tHigh))
-        return(0);      // conversion error
+	return(0);      // conversion error
 
     lTime = ((LONGLONG)hi << 32) + (LONGLONG)low;
     lTime = lTime * 10000;      // convert to multiple of 100ns
@@ -766,7 +766,7 @@
     UINT hi = __unsignedLongIntVal(tHigh);
 
     if (hi == 0 && !__isSmallInteger(tHigh))
-        return(0);      // conversion error
+	return(0);      // conversion error
 
     lTime = ((LONGLONG)hi << 32) + (LONGLONG)low;
     lTime += (LONGLONG)11644473600000L;  // rebias to 1.1.1601
@@ -786,7 +786,7 @@
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
  COPYRIGHT (c) 1998-2004 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -818,90 +818,90 @@
 
     [Class variables:]
 
-        HostName        <String>        remembered hostname
-
-        DomainName      <String>        remembered domainname
-
-        CurrentDirectory <String>       remembered currentDirectories path
+	HostName        <String>        remembered hostname
+
+	DomainName      <String>        remembered domainname
+
+	CurrentDirectory <String>       remembered currentDirectories path
 
     [author:]
-        Claus Gittinger (initial version & cleanup)
-        Manfred Dierolf (many features)
+	Claus Gittinger (initial version & cleanup)
+	Manfred Dierolf (many features)
 
     [see also:]
-        OSProcessStatus
-        Filename Date Time
-        ExternalStream FileStream PipeStream Socket
+	OSProcessStatus
+	Filename Date Time
+	ExternalStream FileStream PipeStream Socket
 "
 !
 
 examples
 "
   various queries
-                                                                [exBegin]
+								[exBegin]
     Transcript
-        showCR:'hello ' , (OperatingSystem getLoginName)
-                                                                [exEnd]
-
-                                                                [exBegin]
+	showCR:'hello ' , (OperatingSystem getLoginName)
+								[exEnd]
+
+								[exBegin]
     OperatingSystem isUNIXlike ifTrue:[
-        Transcript showCR:'this is some UNIX-like OS'
+	Transcript showCR:'this is some UNIX-like OS'
     ] ifFalse:[
-        Transcript showCR:'this OS is not UNIX-like'
+	Transcript showCR:'this OS is not UNIX-like'
     ]
-                                                                [exEnd]
-
-                                                                [exBegin]
+								[exEnd]
+
+								[exBegin]
     Transcript
-        showCR:'this machine is called ' , OperatingSystem getHostName
-                                                                [exEnd]
-
-                                                                [exBegin]
+	showCR:'this machine is called ' , OperatingSystem getHostName
+								[exEnd]
+
+								[exBegin]
     Transcript
-        showCR:('this machine is in the '
-               , OperatingSystem getDomainName
-               , ' domain')
-                                                                [exEnd]
-
-                                                                [exBegin]
+	showCR:('this machine is in the '
+	       , OperatingSystem getDomainName
+	       , ' domain')
+								[exEnd]
+
+								[exBegin]
     Transcript
-        showCR:('this machine''s CPU is a '
-               , OperatingSystem getCPUType
-               )
-                                                                [exEnd]
-
-                                                                [exBegin]
+	showCR:('this machine''s CPU is a '
+	       , OperatingSystem getCPUType
+	       )
+								[exEnd]
+
+								[exBegin]
     Transcript showCR:'executing ls command ...'.
     OperatingSystem executeCommand:'ls'.
     Transcript showCR:'... done.'.
-                                                                [exEnd]
+								[exEnd]
 
   locking a file
   (should be executed on two running smalltalks - not in two threads):
-                                                                [exBegin]
+								[exBegin]
     |f|
 
     f := 'testFile' asFilename readWriteStream.
 
     10 timesRepeat:[
-        'about to lock ...' printCR.
-        [
-          OperatingSystem
-            lockFD:(f fileDescriptor)
-            shared:false
-            blocking:false
-        ] whileFalse:[
-            'process ' print. OperatingSystem getProcessId print. ' is waiting' printCR.
-            Delay waitForSeconds:1
-        ].
-        'LOCKED ...' printCR.
-        Delay waitForSeconds:10.
-        'unlock ...' printCR.
-        (OperatingSystem
-            unlockFD:(f fileDescriptor)) printCR.
-        Delay waitForSeconds:3.
+	'about to lock ...' printCR.
+	[
+	  OperatingSystem
+	    lockFD:(f fileDescriptor)
+	    shared:false
+	    blocking:false
+	] whileFalse:[
+	    'process ' print. OperatingSystem getProcessId print. ' is waiting' printCR.
+	    Delay waitForSeconds:1
+	].
+	'LOCKED ...' printCR.
+	Delay waitForSeconds:10.
+	'unlock ...' printCR.
+	(OperatingSystem
+	    unlockFD:(f fileDescriptor)) printCR.
+	Delay waitForSeconds:3.
     ]
-                                                                [exBegin]
+								[exBegin]
 "
 ! !
 
@@ -913,16 +913,16 @@
 
     if( ! coInitialized ) {
 
-        hres = CoInitializeEx(NULL, COINIT_MULTITHREADED);
-        if (! SUCCEEDED(hres)) {
-            console_fprintf(stderr, "OperatingSystem [info]: Could not open the COM library hres = %08x\n", hres );
-            goto error;
-        }
-        coInitialized = 1;
+	hres = CoInitializeEx(NULL, COINIT_MULTITHREADED);
+	if (! SUCCEEDED(hres)) {
+	    console_fprintf(stderr, "OperatingSystem [info]: Could not open the COM library hres = %08x\n", hres );
+	    goto error;
+	}
+	coInitialized = 1;
 
 #ifdef COM_DEBUG
 
-        console_fprintf(stderr, "OperatingSystem [info]: COM initialized\n" );
+	console_fprintf(stderr, "OperatingSystem [info]: COM initialized\n" );
 #endif
     }
     RETURN (self );
@@ -949,13 +949,13 @@
 
     "/ attention: must be ok to be called twice during startup.
     Initialized isNil ifTrue:[
-        Initialized := true.
-        ObjectMemory addDependent:self.
-        HostName := nil.
-        DomainName := nil.
-        LastErrorNumber := nil.
-        PipeFailed := false.
-        self coInitialize.
+	Initialized := true.
+	ObjectMemory addDependent:self.
+	HostName := nil.
+	DomainName := nil.
+	LastErrorNumber := nil.
+	PipeFailed := false.
+	self coInitialize.
     ].
 
     "Modified: 13.9.1997 / 10:47:32 / cg"
@@ -965,14 +965,14 @@
     "catch image restart and flush some cached data"
 
     something == #earlyRestart ifTrue:[
-        "
-         flush cached data
-        "
-        HostName := nil.
-        DomainName := nil.
-        LastErrorNumber := nil.
-        PipeFailed := false.
-        self coInitialize.
+	"
+	 flush cached data
+	"
+	HostName := nil.
+	DomainName := nil.
+	LastErrorNumber := nil.
+	PipeFailed := false.
+	self coInitialize.
     ]
 
     "Modified: 22.4.1996 / 13:10:43 / cg"
@@ -980,6 +980,7 @@
     "Modified: 7.1.1997 / 19:36:11 / stefan"
 ! !
 
+
 !Win32OperatingSystem class methodsFor:'OS signal constants'!
 
 sigABRT
@@ -1566,7 +1567,7 @@
 
     lp = __win32_getLogFilename();
     if (lp) {
-        ret = __MKSTRING(lp);
+	ret = __MKSTRING(lp);
     }
 %}.
     ^ ret
@@ -1584,16 +1585,16 @@
     |logFilePath|
 
     aFilenameOrNil notNil ifTrue:[
-        logFilePath := aFilenameOrNil asFilename pathName
+	logFilePath := aFilenameOrNil asFilename pathName
     ].
 
 %{
     extern void __win32_setLogFile();
 
     if (__isStringLike(logFilePath)) {
-        __win32_setLogFile(__stringVal(logFilePath));
+	__win32_setLogFile(__stringVal(logFilePath));
     } else {
-        __win32_setLogFile( NULL );
+	__win32_setLogFile( NULL );
     }
 %}
 
@@ -1612,14 +1613,14 @@
 !Win32OperatingSystem class methodsFor:'clipboard'!
 
 clipboardContainsBitmap
-        "Answer whether the clipboard contains a bitmap."
+	"Answer whether the clipboard contains a bitmap."
 
     ^self clipboardContainsFormat: 2 "CfBitmap"
 !
 
 clipboardContainsFormat: aCfConstant
-        "Answer true if the clipboard contains data in
-         the format described by aCfConstant.  "
+	"Answer true if the clipboard contains data in
+	 the format described by aCfConstant.  "
 
     ^self primIsClipboardFormatAvailable: aCfConstant
 !
@@ -1632,7 +1633,7 @@
 !
 
 emptyClipboard
-        "Private - empty the clipboard. Note: it must be opened first."
+	"Private - empty the clipboard. Note: it must be opened first."
     | result |
     result := self primEmptyClipboard.
     result ifFalse: [ ^self error].
@@ -1693,7 +1694,7 @@
 !
 
 setBitmapToClipboard: aBitmap
-        "Copy aBitmap to the clipboard."
+	"Copy aBitmap to the clipboard."
     | handle |
     aBitmap isNil ifTrue:[ ^nil ].
     aBitmap id isNil ifTrue:[aBitmap onDevice: Screen current].
@@ -1705,7 +1706,7 @@
     self closeClipboard
 
     "
-        self setBitmapToClipboard: Image fromUser
+	self setBitmapToClipboard: Image fromUser
     "
 !
 
@@ -1725,47 +1726,47 @@
     int    __modeBits = 0;
 
     if (__fileAttr & FILE_ATTRIBUTE_DIRECTORY) {
-        type = @symbol(directory);
-        __modeBits = 0777;   /* executable and WRITABLE - refer to comment in #isWritable: */
+	type = @symbol(directory);
+	__modeBits = 0777;   /* executable and WRITABLE - refer to comment in #isWritable: */
     } else if (__fileAttr & FILE_ATTRIBUTE_REPARSE_POINT) {
-        type = @symbol(symbolicLink);
-        __modeBits = 0777;   /* even in UNIX symlinks have 0777 */
+	type = @symbol(symbolicLink);
+	__modeBits = 0777;   /* even in UNIX symlinks have 0777 */
     } else {
-        type = @symbol(regular);
-        if (__fileAttr & FILE_ATTRIBUTE_READONLY) {
-            __modeBits = 0444;
-        } else {
-            __modeBits = 0666;
-        }
+	type = @symbol(regular);
+	if (__fileAttr & FILE_ATTRIBUTE_READONLY) {
+	    __modeBits = 0444;
+	} else {
+	    __modeBits = 0666;
+	}
     }
     modeBits = __mkSmallInteger(__modeBits);
 
 %}.
     osCrtTime isNil
-        ifTrue: [crtTime := Timestamp now]
-        ifFalse:[crtTime := Timestamp new fromOSTime:(osCrtTime "- OperatingSystem osTimeOf19700101 -- already done")].
+	ifTrue: [crtTime := Timestamp now]
+	ifFalse:[crtTime := Timestamp new fromOSTime:(osCrtTime "- OperatingSystem osTimeOf19700101 -- already done")].
 
     osAccTime isNil
-        ifTrue: [accTime := Timestamp now]
-        ifFalse:[accTime := Timestamp new fromOSTime:(osAccTime "- OperatingSystem osTimeOf19700101 -- already done")].
+	ifTrue: [accTime := Timestamp now]
+	ifFalse:[accTime := Timestamp new fromOSTime:(osAccTime "- OperatingSystem osTimeOf19700101 -- already done")].
 
     osModTime isNil
-        ifTrue: [modTime := accTime]
-        ifFalse:[modTime := Timestamp new fromOSTime:(osModTime "- OperatingSystem osTimeOf19700101 -- already done")].
+	ifTrue: [modTime := accTime]
+	ifFalse:[modTime := Timestamp new fromOSTime:(osModTime "- OperatingSystem osTimeOf19700101 -- already done")].
 
     ^ FileStatusInfo
-                type:type
-                mode:modeBits
-                uid:nil
-                gid:nil
-                size:fileSize
-                id:0
-                accessed:accTime
-                modified:modTime
-                created:crtTime
-                sourcePath:osPathname
-                fullName:nil
-                alternativeName:nil.
+		type:type
+		mode:modeBits
+		uid:nil
+		gid:nil
+		size:fileSize
+		id:0
+		accessed:accTime
+		modified:modTime
+		created:crtTime
+		sourcePath:osPathname
+		fullName:nil
+		alternativeName:nil.
 !
 
 nextLinkInfoFrom:aDirectoryStream dirPointer:dirPointer
@@ -1780,46 +1781,46 @@
 
     if ((dirPointer != nil)
     && __isExternalAddressLike(dirPointer)) {
-        // __INST(lastErrorNumber) = nil;
-        d = _HANDLEVal(dirPointer);
-
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            rslt = (int)(STX_API_NOINT_CALL2( "FindNextFileW", FindNextFileW, d, &data ));
-        } while ((rslt < 0) && (__threadErrno == EINTR));
-
-        if (rslt > 0) {
-            fileSize  = __MKLARGEINT64(1, data.nFileSizeLow, data.nFileSizeHigh);
-            osPathname = __mkStringOrU16String_maxlen( data.cFileName, MAXPATHLEN );
-            osFileAttributes = __mkSmallInteger( data.dwFileAttributes );
-
-            osCrtTime = FileTimeToOsTime1970(&data.ftCreationTime);
-            osAccTime = FileTimeToOsTime1970(&data.ftLastAccessTime);
-            osModTime = FileTimeToOsTime1970(&data.ftLastWriteTime);
-
-        } else {
-            error = __mkSmallInteger( __threadErrno );
-        }
+	// __INST(lastErrorNumber) = nil;
+	d = _HANDLEVal(dirPointer);
+
+	do {
+	    __threadErrno = 0;
+	    // do not cast to INT - will loose sign bit then!
+	    rslt = (int)(STX_API_NOINT_CALL2( "FindNextFileW", FindNextFileW, d, &data ));
+	} while ((rslt < 0) && (__threadErrno == EINTR));
+
+	if (rslt > 0) {
+	    fileSize  = __MKLARGEINT64(1, data.nFileSizeLow, data.nFileSizeHigh);
+	    osPathname = __mkStringOrU16String_maxlen( data.cFileName, MAXPATHLEN );
+	    osFileAttributes = __mkSmallInteger( data.dwFileAttributes );
+
+	    osCrtTime = FileTimeToOsTime1970(&data.ftCreationTime);
+	    osAccTime = FileTimeToOsTime1970(&data.ftLastAccessTime);
+	    osModTime = FileTimeToOsTime1970(&data.ftLastWriteTime);
+
+	} else {
+	    error = __mkSmallInteger( __threadErrno );
+	}
     }
 %}.
     (error notNil and:[error ~~ 0]) ifTrue:[
-        ^ StreamIOError newException
-            errorCode:error;
-            osErrorHolder:(OperatingSystem errorHolderForNumber:error);
-            parameter:aDirectoryStream;
-            raiseRequest
+	^ StreamIOError newException
+	    errorCode:error;
+	    osErrorHolder:(OperatingSystem errorHolderForNumber:error);
+	    parameter:aDirectoryStream;
+	    raiseRequest
     ].
 
     osPathname isNil ifTrue:[^ nil].
 
     ^ self
-        linkInfoFor:osPathname
-        fileSize:fileSize
-        fileAttributes:osFileAttributes
-        osCrtTime:osCrtTime
-        osAccTime:osAccTime
-        osModTime:osModTime
+	linkInfoFor:osPathname
+	fileSize:fileSize
+	fileAttributes:osFileAttributes
+	osCrtTime:osCrtTime
+	osAccTime:osAccTime
+	osModTime:osModTime
 ! !
 
 !Win32OperatingSystem class methodsFor:'error messages'!
@@ -1856,872 +1857,872 @@
       int __eno = __unsignedLongIntVal(errNr);
 
       if (__isWIN32Error(__eno)) {
-        switch (__eno & 0xFFFF) {
-            /*
-             * WIN32 GetLastError returns
-             */
-            case ERROR_INVALID_FUNCTION:
-                sym = @symbol(ERROR_INVALID_FUNCTION);
-                typ = @symbol(illegalOperationSignal);
-                break;
-
-            case ERROR_BAD_FORMAT:
-                sym = @symbol(ERROR_BAD_FORMAT);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
-
-            case ERROR_FILE_NOT_FOUND:
-                sym = @symbol(ERROR_FILE_NOT_FOUND);
-                typ = @symbol(nonexistentSignal);
-                break;
-
-            case ERROR_PATH_NOT_FOUND:
-                sym = @symbol(ERROR_PATH_NOT_FOUND);
-                typ = @symbol(nonexistentSignal);
-                break;
-
-            case ERROR_TOO_MANY_OPEN_FILES:
-                sym = @symbol(ERROR_TOO_MANY_OPEN_FILES);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            /*
-             * what a nice errorCode - thats the most "useful" one I ever
-             * encountered ... (... those stupid micro-softies ...)
-             */
-            case ERROR_OPEN_FAILED:
-                sym = @symbol(ERROR_OPEN_FAILED);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_ACCESS_DENIED:
-                sym = @symbol(ERROR_ACCESS_DENIED);
-                typ = @symbol(noPermissionsSignal);
-                break;
-
-            case ERROR_INVALID_HANDLE:
-                sym = @symbol(ERROR_INVALID_HANDLE);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
-
-            case ERROR_NOT_ENOUGH_MEMORY:
-                sym = @symbol(ERROR_NOT_ENOUGH_MEMORY);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_NO_SYSTEM_RESOURCES:
-                sym = @symbol(ERROR_NO_SYSTEM_RESOURCES);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_NONPAGED_SYSTEM_RESOURCES:
-                sym = @symbol(ERROR_NONPAGED_SYSTEM_RESOURCES);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_PAGED_SYSTEM_RESOURCES:
-                sym = @symbol(ERROR_PAGED_SYSTEM_RESOURCES);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_INVALID_ACCESS:
-                sym = @symbol(ERROR_INVALID_ACCESS);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
-
-            case ERROR_INVALID_DATA:
-                sym = @symbol(ERROR_INVALID_DATA);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
-
-            case ERROR_INVALID_NAME:
-                sym = @symbol(ERROR_INVALID_NAME);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
-
-            case ERROR_ARENA_TRASHED:
-                sym = @symbol(ERROR_ARENA_TRASHED);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_OUTOFMEMORY:
-                sym = @symbol(ERROR_OUTOFMEMORY);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_BROKEN_PIPE:
-                sym = @symbol(ERROR_BROKEN_PIPE);
-                typ = @symbol(peerFaultSignal);
-                break;
-
-            case ERROR_GEN_FAILURE:
-                sym = @symbol(ERROR_GEN_FAILURE);
-                break;
-
-            case ERROR_WRITE_PROTECT:
-                sym = @symbol(ERROR_WRITE_PROTECT);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
-
-            case ERROR_WRITE_FAULT:
-                sym = @symbol(ERROR_WRITE_FAULT);
-                typ = @symbol(transferFaultSignal);
-                break;
-
-            case ERROR_READ_FAULT:
-                sym = @symbol(ERROR_READ_FAULT);
-                typ = @symbol(transferFaultSignal);
-                break;
-
-            case ERROR_HANDLE_DISK_FULL:
-                sym = @symbol(ERROR_HANDLE_DISK_FULL);
-                typ = @symbol(volumeFullSignal);
-                break;
-
-            case ERROR_DISK_FULL:
-                sym = @symbol(ERROR_DISK_FULL);
-                typ = @symbol(volumeFullSignal);
-                break;
-
-            case ERROR_SHARING_VIOLATION:
-                sym = @symbol(ERROR_SHARING_VIOLATION);
-                typ = @symbol(noPermissionsSignal);
-                break;
-
-            case ERROR_LOCK_VIOLATION:
-                sym = @symbol(ERROR_LOCK_VIOLATION);
-                typ = @symbol(noPermissionsSignal);
-                break;
-
-            case ERROR_INVALID_PARAMETER:
-                sym = @symbol(ERROR_INVALID_PARAMETER);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
-
-            case ERROR_NET_WRITE_FAULT:
-                sym = @symbol(ERROR_NET_WRITE_FAULT);
-                typ = @symbol(transferFaultSignal);
-                break;
-
-            case ERROR_NOT_SUPPORTED:
-                sym = @symbol(ERROR_NOT_SUPPORTED);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
-
-            case ERROR_REM_NOT_LIST:
-                sym = @symbol(ERROR_REM_NOT_LIST);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_NETWORK_ACCESS_DENIED:
-                sym = @symbol(ERROR_NETWORK_ACCESS_DENIED);
-                typ = @symbol(noPermissionsSignal);
-                break;
-
-            case ERROR_DUP_NAME:
-                sym = @symbol(ERROR_DUP_NAME);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_BAD_NETPATH:
-                sym = @symbol(ERROR_BAD_NETPATH);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_NETWORK_BUSY:
-                sym = @symbol(ERROR_NETWORK_BUSY);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_DRIVE_LOCKED:
-                sym = @symbol(ERROR_DRIVE_LOCKED);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
-
-            case ERROR_INVALID_DRIVE:
-                sym = @symbol(ERROR_INVALID_DRIVE);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
-
-            case ERROR_WRONG_DISK:
-                sym = @symbol(ERROR_WRONG_DISK);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_CURRENT_DIRECTORY:
-                sym = @symbol(ERROR_CURRENT_DIRECTORY);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
-
-            /*
-             * what a nice errorCode - thats the most "useful" one I ever
-             * encountered ... (... those stupid micro-softies ...)
-             */
-            case ERROR_CANNOT_MAKE:
-                sym = @symbol(ERROR_CANNOT_MAKE);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
-
-            case ERROR_NO_MORE_FILES:
-                sym = @symbol(ERROR_NO_MORE_FILES);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_NOT_READY:
-                sym = @symbol(ERROR_NOT_READY);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_NOT_DOS_DISK:
-                sym = @symbol(ERROR_NOT_DOS_DISK);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
-
-            case ERROR_OUT_OF_PAPER:
-                sym = @symbol(ERROR_OUT_OF_PAPER);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_PRINTQ_FULL:
-                sym = @symbol(ERROR_PRINTQ_FULL);
-                typ = @symbol(noResourcesSignal);
-                break;
-
-            case ERROR_FILE_EXISTS:
-                sym = @symbol(ERROR_FILE_EXISTS);
-                typ = @symbol(existingReferentSignal);
-                break;
-
-            default:
-                break;
-        }
+	switch (__eno & 0xFFFF) {
+	    /*
+	     * WIN32 GetLastError returns
+	     */
+	    case ERROR_INVALID_FUNCTION:
+		sym = @symbol(ERROR_INVALID_FUNCTION);
+		typ = @symbol(illegalOperationSignal);
+		break;
+
+	    case ERROR_BAD_FORMAT:
+		sym = @symbol(ERROR_BAD_FORMAT);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
+
+	    case ERROR_FILE_NOT_FOUND:
+		sym = @symbol(ERROR_FILE_NOT_FOUND);
+		typ = @symbol(nonexistentSignal);
+		break;
+
+	    case ERROR_PATH_NOT_FOUND:
+		sym = @symbol(ERROR_PATH_NOT_FOUND);
+		typ = @symbol(nonexistentSignal);
+		break;
+
+	    case ERROR_TOO_MANY_OPEN_FILES:
+		sym = @symbol(ERROR_TOO_MANY_OPEN_FILES);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    /*
+	     * what a nice errorCode - thats the most "useful" one I ever
+	     * encountered ... (... those stupid micro-softies ...)
+	     */
+	    case ERROR_OPEN_FAILED:
+		sym = @symbol(ERROR_OPEN_FAILED);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_ACCESS_DENIED:
+		sym = @symbol(ERROR_ACCESS_DENIED);
+		typ = @symbol(noPermissionsSignal);
+		break;
+
+	    case ERROR_INVALID_HANDLE:
+		sym = @symbol(ERROR_INVALID_HANDLE);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
+
+	    case ERROR_NOT_ENOUGH_MEMORY:
+		sym = @symbol(ERROR_NOT_ENOUGH_MEMORY);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_NO_SYSTEM_RESOURCES:
+		sym = @symbol(ERROR_NO_SYSTEM_RESOURCES);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_NONPAGED_SYSTEM_RESOURCES:
+		sym = @symbol(ERROR_NONPAGED_SYSTEM_RESOURCES);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_PAGED_SYSTEM_RESOURCES:
+		sym = @symbol(ERROR_PAGED_SYSTEM_RESOURCES);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_INVALID_ACCESS:
+		sym = @symbol(ERROR_INVALID_ACCESS);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
+
+	    case ERROR_INVALID_DATA:
+		sym = @symbol(ERROR_INVALID_DATA);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
+
+	    case ERROR_INVALID_NAME:
+		sym = @symbol(ERROR_INVALID_NAME);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
+
+	    case ERROR_ARENA_TRASHED:
+		sym = @symbol(ERROR_ARENA_TRASHED);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_OUTOFMEMORY:
+		sym = @symbol(ERROR_OUTOFMEMORY);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_BROKEN_PIPE:
+		sym = @symbol(ERROR_BROKEN_PIPE);
+		typ = @symbol(peerFaultSignal);
+		break;
+
+	    case ERROR_GEN_FAILURE:
+		sym = @symbol(ERROR_GEN_FAILURE);
+		break;
+
+	    case ERROR_WRITE_PROTECT:
+		sym = @symbol(ERROR_WRITE_PROTECT);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
+
+	    case ERROR_WRITE_FAULT:
+		sym = @symbol(ERROR_WRITE_FAULT);
+		typ = @symbol(transferFaultSignal);
+		break;
+
+	    case ERROR_READ_FAULT:
+		sym = @symbol(ERROR_READ_FAULT);
+		typ = @symbol(transferFaultSignal);
+		break;
+
+	    case ERROR_HANDLE_DISK_FULL:
+		sym = @symbol(ERROR_HANDLE_DISK_FULL);
+		typ = @symbol(volumeFullSignal);
+		break;
+
+	    case ERROR_DISK_FULL:
+		sym = @symbol(ERROR_DISK_FULL);
+		typ = @symbol(volumeFullSignal);
+		break;
+
+	    case ERROR_SHARING_VIOLATION:
+		sym = @symbol(ERROR_SHARING_VIOLATION);
+		typ = @symbol(noPermissionsSignal);
+		break;
+
+	    case ERROR_LOCK_VIOLATION:
+		sym = @symbol(ERROR_LOCK_VIOLATION);
+		typ = @symbol(noPermissionsSignal);
+		break;
+
+	    case ERROR_INVALID_PARAMETER:
+		sym = @symbol(ERROR_INVALID_PARAMETER);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
+
+	    case ERROR_NET_WRITE_FAULT:
+		sym = @symbol(ERROR_NET_WRITE_FAULT);
+		typ = @symbol(transferFaultSignal);
+		break;
+
+	    case ERROR_NOT_SUPPORTED:
+		sym = @symbol(ERROR_NOT_SUPPORTED);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
+
+	    case ERROR_REM_NOT_LIST:
+		sym = @symbol(ERROR_REM_NOT_LIST);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_NETWORK_ACCESS_DENIED:
+		sym = @symbol(ERROR_NETWORK_ACCESS_DENIED);
+		typ = @symbol(noPermissionsSignal);
+		break;
+
+	    case ERROR_DUP_NAME:
+		sym = @symbol(ERROR_DUP_NAME);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_BAD_NETPATH:
+		sym = @symbol(ERROR_BAD_NETPATH);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_NETWORK_BUSY:
+		sym = @symbol(ERROR_NETWORK_BUSY);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_DRIVE_LOCKED:
+		sym = @symbol(ERROR_DRIVE_LOCKED);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
+
+	    case ERROR_INVALID_DRIVE:
+		sym = @symbol(ERROR_INVALID_DRIVE);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
+
+	    case ERROR_WRONG_DISK:
+		sym = @symbol(ERROR_WRONG_DISK);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_CURRENT_DIRECTORY:
+		sym = @symbol(ERROR_CURRENT_DIRECTORY);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
+
+	    /*
+	     * what a nice errorCode - thats the most "useful" one I ever
+	     * encountered ... (... those stupid micro-softies ...)
+	     */
+	    case ERROR_CANNOT_MAKE:
+		sym = @symbol(ERROR_CANNOT_MAKE);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
+
+	    case ERROR_NO_MORE_FILES:
+		sym = @symbol(ERROR_NO_MORE_FILES);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_NOT_READY:
+		sym = @symbol(ERROR_NOT_READY);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_NOT_DOS_DISK:
+		sym = @symbol(ERROR_NOT_DOS_DISK);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
+
+	    case ERROR_OUT_OF_PAPER:
+		sym = @symbol(ERROR_OUT_OF_PAPER);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_PRINTQ_FULL:
+		sym = @symbol(ERROR_PRINTQ_FULL);
+		typ = @symbol(noResourcesSignal);
+		break;
+
+	    case ERROR_FILE_EXISTS:
+		sym = @symbol(ERROR_FILE_EXISTS);
+		typ = @symbol(existingReferentSignal);
+		break;
+
+	    default:
+		break;
+	}
       } else {
-        switch (__eno) {
-            /*
-             * POSIX errnos - these should be defined
-             */
+	switch (__eno) {
+	    /*
+	     * POSIX errnos - these should be defined
+	     */
 #ifdef EPERM
-            case EPERM:
-                sym = @symbol(EPERM);
-                typ = @symbol(noPermissionsSignal);
-                break;
+	    case EPERM:
+		sym = @symbol(EPERM);
+		typ = @symbol(noPermissionsSignal);
+		break;
 #endif
 #ifdef ENOENT
-            case ENOENT:
-                sym = @symbol(ENOENT);
-                typ = @symbol(nonexistentSignal);
-                break;
+	    case ENOENT:
+		sym = @symbol(ENOENT);
+		typ = @symbol(nonexistentSignal);
+		break;
 #endif
 #ifdef ESRCH
-            case ESRCH:
-                sym = @symbol(ESRCH);
-                typ = @symbol(unavailableReferentSignal);
-                break;
+	    case ESRCH:
+		sym = @symbol(ESRCH);
+		typ = @symbol(unavailableReferentSignal);
+		break;
 #endif
 #ifdef EINTR
-            case EINTR:
-                sym = @symbol(EINTR);
-                typ = @symbol(transientErrorSignal);
-                break;
+	    case EINTR:
+		sym = @symbol(EINTR);
+		typ = @symbol(transientErrorSignal);
+		break;
 #endif
 #ifdef EIO
-            case EIO:
-                sym = @symbol(EIO);
-                typ = @symbol(transferFaultSignal);
-                break;
+	    case EIO:
+		sym = @symbol(EIO);
+		typ = @symbol(transferFaultSignal);
+		break;
 #endif
 #ifdef ENXIO
-            case ENXIO:
-                sym = @symbol(ENXIO);
-                typ = @symbol(unavailableReferentSignal);
-                break;
+	    case ENXIO:
+		sym = @symbol(ENXIO);
+		typ = @symbol(unavailableReferentSignal);
+		break;
 #endif
 #ifdef E2BIG
-            case E2BIG:
-                sym = @symbol(E2BIG);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
+	    case E2BIG:
+		sym = @symbol(E2BIG);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
 #endif
 #ifdef ENOEXEC
-            case ENOEXEC:
-                sym = @symbol(ENOEXEC);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
+	    case ENOEXEC:
+		sym = @symbol(ENOEXEC);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
 #endif
 #ifdef EBADF
-            case EBADF:
-                sym = @symbol(EBADF);
-                typ = @symbol(badAccessorSignal);
-                break;
+	    case EBADF:
+		sym = @symbol(EBADF);
+		typ = @symbol(badAccessorSignal);
+		break;
 #endif
 #ifdef ECHILD
-            case ECHILD:
-                sym = @symbol(ECHILD);
-                typ = @symbol(informationSignal);
-                break;
+	    case ECHILD:
+		sym = @symbol(ECHILD);
+		typ = @symbol(informationSignal);
+		break;
 #endif
 #if !defined(EWOULDBLOCK) && defined(EAGAIN) && (EWOULDBLOCK != EAGAIN)
-            case EAGAIN:
-                sym = @symbol(EAGAIN);
-                typ = @symbol(notReadySignal);
-                break;
+	    case EAGAIN:
+		sym = @symbol(EAGAIN);
+		typ = @symbol(notReadySignal);
+		break;
 #endif
 #ifdef ENOMEM
-            case ENOMEM:
-                sym = @symbol(ENOMEM);
-                typ = @symbol(noMemorySignal);
-                break;
+	    case ENOMEM:
+		sym = @symbol(ENOMEM);
+		typ = @symbol(noMemorySignal);
+		break;
 #endif
 #ifdef EACCES
-            case EACCES:
-                sym = @symbol(EACCES);
-                typ = @symbol(noPermissionsSignal);
-                break;
+	    case EACCES:
+		sym = @symbol(EACCES);
+		typ = @symbol(noPermissionsSignal);
+		break;
 #endif
 #ifdef EFAULT
-            case EFAULT:
-                sym = @symbol(EFAULT);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
+	    case EFAULT:
+		sym = @symbol(EFAULT);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
 #endif
 #ifdef EBUSY
-            case EBUSY:
-                sym = @symbol(EBUSY);
-                typ = @symbol(unavailableReferentSignal);
-                break;
+	    case EBUSY:
+		sym = @symbol(EBUSY);
+		typ = @symbol(unavailableReferentSignal);
+		break;
 #endif
 #ifdef EEXIST
-            case EEXIST:
-                sym = @symbol(EEXIST);
-                typ = @symbol(existingReferentSignal);
-                break;
+	    case EEXIST:
+		sym = @symbol(EEXIST);
+		typ = @symbol(existingReferentSignal);
+		break;
 #endif
 #ifdef EXDEV
-            case EXDEV:
-                sym = @symbol(EXDEV);
-                typ = @symbol(inappropriateReferentSignal);
-                break;
+	    case EXDEV:
+		sym = @symbol(EXDEV);
+		typ = @symbol(inappropriateReferentSignal);
+		break;
 #endif
 #ifdef ENODEV
-            case ENODEV:
-                sym = @symbol(ENODEV);
-                typ = @symbol(inaccessibleSignal);
-                break;
+	    case ENODEV:
+		sym = @symbol(ENODEV);
+		typ = @symbol(inaccessibleSignal);
+		break;
 #endif
 #ifdef ENOTDIR
-            case ENOTDIR:
-                sym = @symbol(ENOTDIR);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
+	    case ENOTDIR:
+		sym = @symbol(ENOTDIR);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
 #endif
 #ifdef EISDIR
-            case EISDIR:
-                sym = @symbol(EISDIR);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
+	    case EISDIR:
+		sym = @symbol(EISDIR);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
 #endif
 #ifdef EINVAL
-            case EINVAL:
-                sym = @symbol(EINVAL);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
+	    case EINVAL:
+		sym = @symbol(EINVAL);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
 #endif
 #ifdef ENFILE
-            case ENFILE:
-                sym = @symbol(ENFILE);
-                typ = @symbol(noResourcesSignal);
-                break;
+	    case ENFILE:
+		sym = @symbol(ENFILE);
+		typ = @symbol(noResourcesSignal);
+		break;
 #endif
 #ifdef EMFILE
-            case EMFILE:
-                sym = @symbol(EMFILE);
-                typ = @symbol(noResourcesSignal);
-                break;
+	    case EMFILE:
+		sym = @symbol(EMFILE);
+		typ = @symbol(noResourcesSignal);
+		break;
 #endif
 #ifdef ENOTTY
-            case ENOTTY:
-                sym = @symbol(ENOTTY);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
+	    case ENOTTY:
+		sym = @symbol(ENOTTY);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
 #endif
 #ifdef EFBIG
-            case EFBIG:
-                sym = @symbol(EFBIG);
-                typ = @symbol(noResourcesSignal);
-                break;
+	    case EFBIG:
+		sym = @symbol(EFBIG);
+		typ = @symbol(noResourcesSignal);
+		break;
 #endif
 #ifdef ENOSPC
-            case ENOSPC:
-                sym = @symbol(ENOSPC);
-                typ = @symbol(noResourcesSignal);
-                break;
+	    case ENOSPC:
+		sym = @symbol(ENOSPC);
+		typ = @symbol(noResourcesSignal);
+		break;
 #endif
 #ifdef ESPIPE
-            case ESPIPE:
-                sym = @symbol(ESPIPE);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
+	    case ESPIPE:
+		sym = @symbol(ESPIPE);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
 #endif
 #ifdef EROFS
-            case EROFS:
-                sym = @symbol(EROFS);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
+	    case EROFS:
+		sym = @symbol(EROFS);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
 #endif
 #ifdef EMLINK
-            case EMLINK:
-                sym = @symbol(EMLINK);
-                typ = @symbol(rangeErrorSignal);
-                break;
+	    case EMLINK:
+		sym = @symbol(EMLINK);
+		typ = @symbol(rangeErrorSignal);
+		break;
 #endif
 #ifdef EPIPE
-            case EPIPE:
-                sym = @symbol(EPIPE);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case EPIPE:
+		sym = @symbol(EPIPE);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef EDOM
-            case EDOM:
-                sym = @symbol(EDOM);
-                typ = @symbol(rangeErrorSignal);
-                break;
+	    case EDOM:
+		sym = @symbol(EDOM);
+		typ = @symbol(rangeErrorSignal);
+		break;
 #endif
 #ifdef ERANGE
-            case ERANGE:
-                sym = @symbol(ERANGE);
-                typ = @symbol(rangeErrorSignal);
-                break;
+	    case ERANGE:
+		sym = @symbol(ERANGE);
+		typ = @symbol(rangeErrorSignal);
+		break;
 #endif
 #ifdef EDEADLK
 # if EDEADLK != EWOULDBLOCK
-            case EDEADLK:
-                sym = @symbol(EDEADLK);
-                typ = @symbol(noResourcesSignal);
-                break;
+	    case EDEADLK:
+		sym = @symbol(EDEADLK);
+		typ = @symbol(noResourcesSignal);
+		break;
 # endif
 #endif
 #ifdef ENAMETOOLONG
-            case ENAMETOOLONG:
-                sym = @symbol(ENAMETOOLONG);
-                typ = @symbol(rangeErrorSignal);
-                break;
+	    case ENAMETOOLONG:
+		sym = @symbol(ENAMETOOLONG);
+		typ = @symbol(rangeErrorSignal);
+		break;
 #endif
 #ifdef ENOLCK
-            case ENOLCK:
-                sym = @symbol(ENOLCK);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
+	    case ENOLCK:
+		sym = @symbol(ENOLCK);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
 #endif
 #ifdef ENOSYS
-            case ENOSYS:
-                sym = @symbol(ENOSYS);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
+	    case ENOSYS:
+		sym = @symbol(ENOSYS);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
 #endif
 #if defined(ENOTEMPTY) && (ENOTEMPTY != EEXIST)
-            case ENOTEMPTY:
-                sym = @symbol(ENOTEMPTY);
-                typ = @symbol(inappropriateReferentSignal);
-                break;
+	    case ENOTEMPTY:
+		sym = @symbol(ENOTEMPTY);
+		typ = @symbol(inappropriateReferentSignal);
+		break;
 #endif
 #ifdef EILSEQ
-            case EILSEQ:
-                sym = @symbol(EILSEQ);
-                typ = @symbol(transferFaultSignal);
-                break;
-#endif
-            /*
-             * XPG3 errnos - defined on most systems
-             */
+	    case EILSEQ:
+		sym = @symbol(EILSEQ);
+		typ = @symbol(transferFaultSignal);
+		break;
+#endif
+	    /*
+	     * XPG3 errnos - defined on most systems
+	     */
 #ifdef ENOTBLK
-            case ENOTBLK:
-                sym = @symbol(ENOTBLK);
-                typ = @symbol(inappropriateReferentSignal);
-                break;
+	    case ENOTBLK:
+		sym = @symbol(ENOTBLK);
+		typ = @symbol(inappropriateReferentSignal);
+		break;
 #endif
 #ifdef ETXTBSY
-            case ETXTBSY:
-                sym = @symbol(ETXTBSY);
-                typ = @symbol(inaccessibleSignal);
-                break;
-#endif
-            /*
-             * some others
-             */
+	    case ETXTBSY:
+		sym = @symbol(ETXTBSY);
+		typ = @symbol(inaccessibleSignal);
+		break;
+#endif
+	    /*
+	     * some others
+	     */
 #ifdef EWOULDBLOCK
-            case EWOULDBLOCK:
-                sym = @symbol(EWOULDBLOCK);
-                typ = @symbol(notReadySignal);
-                break;
+	    case EWOULDBLOCK:
+		sym = @symbol(EWOULDBLOCK);
+		typ = @symbol(notReadySignal);
+		break;
 #endif
 #ifdef ENOMSG
-            case ENOMSG:
-                sym = @symbol(ENOMSG);
-                typ = @symbol(noDataSignal);
-                break;
+	    case ENOMSG:
+		sym = @symbol(ENOMSG);
+		typ = @symbol(noDataSignal);
+		break;
 #endif
 #ifdef ELOOP
-            case ELOOP:
-                sym = @symbol(ELOOP);
-                typ = @symbol(rangeErrorSignal);
-                break;
-#endif
-
-            /*
-             * some stream errors
-             */
+	    case ELOOP:
+		sym = @symbol(ELOOP);
+		typ = @symbol(rangeErrorSignal);
+		break;
+#endif
+
+	    /*
+	     * some stream errors
+	     */
 #ifdef ETIME
-            case ETIME:
-                sym = @symbol(ETIME);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case ETIME:
+		sym = @symbol(ETIME);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef ENOSR
-            case ENOSR:
-                sym = @symbol(ENOSR);
-                typ = @symbol(noResourcesSignal);
-                break;
+	    case ENOSR:
+		sym = @symbol(ENOSR);
+		typ = @symbol(noResourcesSignal);
+		break;
 #endif
 #ifdef ENOSTR
-            case ENOSTR:
-                sym = @symbol(ENOSTR);
-                typ = @symbol(inappropriateReferentSignal);
-                break;
+	    case ENOSTR:
+		sym = @symbol(ENOSTR);
+		typ = @symbol(inappropriateReferentSignal);
+		break;
 #endif
 #ifdef ECOMM
-            case ECOMM:
-                sym = @symbol(ECOMM);
-                typ = @symbol(transferFaultSignal);
-                break;
+	    case ECOMM:
+		sym = @symbol(ECOMM);
+		typ = @symbol(transferFaultSignal);
+		break;
 #endif
 #ifdef EPROTO
-            case EPROTO:
-                sym = @symbol(EPROTO);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
-#endif
-            /*
-             * nfs errors
-             */
+	    case EPROTO:
+		sym = @symbol(EPROTO);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
+#endif
+	    /*
+	     * nfs errors
+	     */
 #ifdef ESTALE
-            case ESTALE:
-                sym = @symbol(ESTALE);
-                typ = @symbol(unavailableReferentSignal);
-                break;
+	    case ESTALE:
+		sym = @symbol(ESTALE);
+		typ = @symbol(unavailableReferentSignal);
+		break;
 #endif
 #ifdef EREMOTE
-            case EREMOTE:
-                sym = @symbol(EREMOTE);
-                typ = @symbol(rangeErrorSignal);
-                break;
-#endif
-            /*
-             * some networking errors
-             */
+	    case EREMOTE:
+		sym = @symbol(EREMOTE);
+		typ = @symbol(rangeErrorSignal);
+		break;
+#endif
+	    /*
+	     * some networking errors
+	     */
 #ifdef EINPROGRESS
-            case EINPROGRESS:
-                sym = @symbol(EINPROGRESS);
-                typ = @symbol(operationStartedSignal);
-                break;
+	    case EINPROGRESS:
+		sym = @symbol(EINPROGRESS);
+		typ = @symbol(operationStartedSignal);
+		break;
 #endif
 #ifdef EALREADY
-            case EALREADY:
-                sym = @symbol(EALREADY);
-                typ = @symbol(operationStartedSignal);
-                break;
+	    case EALREADY:
+		sym = @symbol(EALREADY);
+		typ = @symbol(operationStartedSignal);
+		break;
 #endif
 #ifdef ENOTSOCK
-            case ENOTSOCK:
-                sym = @symbol(ENOTSOCK);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
+	    case ENOTSOCK:
+		sym = @symbol(ENOTSOCK);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
 #endif
 #ifdef EDESTADDRREQ
-            case EDESTADDRREQ:
-                sym = @symbol(EDESTADDRREQ);
-                typ = @symbol(underspecifiedSignal);
-                break;
+	    case EDESTADDRREQ:
+		sym = @symbol(EDESTADDRREQ);
+		typ = @symbol(underspecifiedSignal);
+		break;
 #endif
 #ifdef EMSGSIZE
-            case EMSGSIZE:
-                sym = @symbol(EMSGSIZE);
-                typ = @symbol(rangeErrorSignal);
-                break;
+	    case EMSGSIZE:
+		sym = @symbol(EMSGSIZE);
+		typ = @symbol(rangeErrorSignal);
+		break;
 #endif
 #ifdef EPROTOTYPE
-            case EPROTOTYPE:
-                sym = @symbol(EPROTOTYPE);
-                typ = @symbol(wrongSubtypeForOperationSignal);
-                break;
+	    case EPROTOTYPE:
+		sym = @symbol(EPROTOTYPE);
+		typ = @symbol(wrongSubtypeForOperationSignal);
+		break;
 #endif
 #ifdef ENOPROTOOPT
-            case ENOPROTOOPT:
-                sym = @symbol(ENOPROTOOPT);
-                typ = @symbol(unsupportedOperationSignal);
-                break;
+	    case ENOPROTOOPT:
+		sym = @symbol(ENOPROTOOPT);
+		typ = @symbol(unsupportedOperationSignal);
+		break;
 #endif
 #ifdef EPROTONOSUPPORT
-            case EPROTONOSUPPORT:
-                sym = @symbol(EPROTONOSUPPORT);
-                typ = @symbol(unsupportedOperationSignal);
-                break;
+	    case EPROTONOSUPPORT:
+		sym = @symbol(EPROTONOSUPPORT);
+		typ = @symbol(unsupportedOperationSignal);
+		break;
 #endif
 #ifdef ESOCKTNOSUPPORT
-            case ESOCKTNOSUPPORT:
-                sym = @symbol(ESOCKTNOSUPPORT);
-                typ = @symbol(unsupportedOperationSignal);
-                break;
+	    case ESOCKTNOSUPPORT:
+		sym = @symbol(ESOCKTNOSUPPORT);
+		typ = @symbol(unsupportedOperationSignal);
+		break;
 #endif
 #ifdef EOPNOTSUPP
-            case EOPNOTSUPP:
-                sym = @symbol(EOPNOTSUPP);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
+	    case EOPNOTSUPP:
+		sym = @symbol(EOPNOTSUPP);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
 #endif
 #ifdef EPFNOSUPPORT
-            case EPFNOSUPPORT:
-                sym = @symbol(EPFNOSUPPORT);
-                typ = @symbol(unsupportedOperationSignal);
-                break;
+	    case EPFNOSUPPORT:
+		sym = @symbol(EPFNOSUPPORT);
+		typ = @symbol(unsupportedOperationSignal);
+		break;
 #endif
 #ifdef EAFNOSUPPORT
-            case EAFNOSUPPORT:
-                sym = @symbol(EAFNOSUPPORT);
-                typ = @symbol(unsupportedOperationSignal);
-                break;
+	    case EAFNOSUPPORT:
+		sym = @symbol(EAFNOSUPPORT);
+		typ = @symbol(unsupportedOperationSignal);
+		break;
 #endif
 #ifdef EADDRINUSE
-            case EADDRINUSE:
-                sym = @symbol(EADDRINUSE);
-                typ = @symbol(existingReferentSignal);
-                break;
+	    case EADDRINUSE:
+		sym = @symbol(EADDRINUSE);
+		typ = @symbol(existingReferentSignal);
+		break;
 #endif
 #ifdef WSAEADDRINUSE
-            case WSAEADDRINUSE:
-                sym = @symbol(WSAEADDRINUSE);
-                typ = @symbol(existingReferentSignal);
-                break;
+	    case WSAEADDRINUSE:
+		sym = @symbol(WSAEADDRINUSE);
+		typ = @symbol(existingReferentSignal);
+		break;
 #endif
 
 #ifdef EADDRNOTAVAIL
-            case EADDRNOTAVAIL:
-                sym = @symbol(EADDRNOTAVAIL);
-                typ = @symbol(noPermissionsSignal);
-                break;
+	    case EADDRNOTAVAIL:
+		sym = @symbol(EADDRNOTAVAIL);
+		typ = @symbol(noPermissionsSignal);
+		break;
 #endif
 #ifdef ETIMEDOUT
-            case ETIMEDOUT:
-                sym = @symbol(ETIMEDOUT);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case ETIMEDOUT:
+		sym = @symbol(ETIMEDOUT);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef WSAETIMEDOUT
-            case WSAETIMEDOUT:
-                sym = @symbol(ETIMEDOUT);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case WSAETIMEDOUT:
+		sym = @symbol(ETIMEDOUT);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef ECONNREFUSED
-            case ECONNREFUSED:
-                sym = @symbol(ECONNREFUSED);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case ECONNREFUSED:
+		sym = @symbol(ECONNREFUSED);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef WSAECONNREFUSED
-            case WSAECONNREFUSED:
-                sym = @symbol(ECONNREFUSED);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case WSAECONNREFUSED:
+		sym = @symbol(ECONNREFUSED);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef ENETDOWN
-            case ENETDOWN:
-                sym = @symbol(ENETDOWN);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case ENETDOWN:
+		sym = @symbol(ENETDOWN);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef ENETUNREACH
-            case ENETUNREACH:
-                sym = @symbol(ENETUNREACH);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case ENETUNREACH:
+		sym = @symbol(ENETUNREACH);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef ENETRESET
-            case ENETRESET:
-                sym = @symbol(ENETRESET);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case ENETRESET:
+		sym = @symbol(ENETRESET);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef ECONNABORTED
-            case ECONNABORTED:
-                sym = @symbol(ECONNABORTED);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case ECONNABORTED:
+		sym = @symbol(ECONNABORTED);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef ECONNRESET
-            case ECONNRESET:
-                sym = @symbol(ECONNRESET);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case ECONNRESET:
+		sym = @symbol(ECONNRESET);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef EISCONN
-            case EISCONN:
-                sym = @symbol(EISCONN);
-                typ = @symbol(unpreparedOperationSignal);
-                break;
+	    case EISCONN:
+		sym = @symbol(EISCONN);
+		typ = @symbol(unpreparedOperationSignal);
+		break;
 #endif
 #ifdef ENOTCONN
-            case ENOTCONN:
-                sym = @symbol(ENOTCONN);
-                typ = @symbol(unpreparedOperationSignal);
-                break;
+	    case ENOTCONN:
+		sym = @symbol(ENOTCONN);
+		typ = @symbol(unpreparedOperationSignal);
+		break;
 #endif
 #ifdef ESHUTDOWN
-            case ESHUTDOWN:
-                sym = @symbol(ESHUTDOWN);
-                typ = @symbol(unpreparedOperationSignal);
-                break;
+	    case ESHUTDOWN:
+		sym = @symbol(ESHUTDOWN);
+		typ = @symbol(unpreparedOperationSignal);
+		break;
 #endif
 #ifdef EHOSTDOWN
-            case EHOSTDOWN:
-                sym = @symbol(EHOSTDOWN);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case EHOSTDOWN:
+		sym = @symbol(EHOSTDOWN);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef EHOSTUNREACH
-            case EHOSTUNREACH:
-                sym = @symbol(EHOSTUNREACH);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case EHOSTUNREACH:
+		sym = @symbol(EHOSTUNREACH);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 #ifdef WSAHOSTUNREACH
-            case WSAHOSTUNREACH:
-                sym = @symbol(EHOSTUNREACH);
-                typ = @symbol(peerFaultSignal);
-                break;
+	    case WSAHOSTUNREACH:
+		sym = @symbol(EHOSTUNREACH);
+		typ = @symbol(peerFaultSignal);
+		break;
 #endif
 
 #ifdef WSAEFAULT
-            case WSAEFAULT:
-                sym = @symbol(WSAEFAULT);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
+	    case WSAEFAULT:
+		sym = @symbol(WSAEFAULT);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
 #endif
 #ifdef WSAEINTR
-            case WSAEINTR:
-                sym = @symbol(WSAEINTR);
-                typ = @symbol(transientErrorSignal);
-                break;
+	    case WSAEINTR:
+		sym = @symbol(WSAEINTR);
+		typ = @symbol(transientErrorSignal);
+		break;
 #endif
 #ifdef WSAEBADF
-            case WSAEBADF:
-                sym = @symbol(WSAEBADF);
-                typ = @symbol(badAccessorSignal);
-                break;
+	    case WSAEBADF:
+		sym = @symbol(WSAEBADF);
+		typ = @symbol(badAccessorSignal);
+		break;
 #endif
 #ifdef WSAEACCES
-            case WSAEACCES:
-                sym = @symbol(WSAEACCES);
-                typ = @symbol(badAccessorSignal);
-                break;
+	    case WSAEACCES:
+		sym = @symbol(WSAEACCES);
+		typ = @symbol(badAccessorSignal);
+		break;
 #endif
 #ifdef WSAEINVAL
-            case WSAEINVAL:
-                sym = @symbol(WSAEINVAL);
-                typ = @symbol(invalidArgumentsSignal);
-                break;
+	    case WSAEINVAL:
+		sym = @symbol(WSAEINVAL);
+		typ = @symbol(invalidArgumentsSignal);
+		break;
 #endif
 #ifdef WSAEMFILE
-            case WSAEMFILE:
-                sym = @symbol(WSAEMFILE);
-                typ = @symbol(noResourcesSignal);
-                break;
+	    case WSAEMFILE:
+		sym = @symbol(WSAEMFILE);
+		typ = @symbol(noResourcesSignal);
+		break;
 #endif
 #ifdef WSAEWOULDBLOCK
-            case WSAEWOULDBLOCK:
-                sym = @symbol(WSAEWOULDBLOCK);
-                typ = @symbol(notReadySignal);
-                break;
+	    case WSAEWOULDBLOCK:
+		sym = @symbol(WSAEWOULDBLOCK);
+		typ = @symbol(notReadySignal);
+		break;
 #endif
 #ifdef WSAEINPROGRESS
-            case WSAEINPROGRESS:
-                sym = @symbol(WSAEINPROGRESS);
-                typ = @symbol(operationStartedSignal);
-                break;
+	    case WSAEINPROGRESS:
+		sym = @symbol(WSAEINPROGRESS);
+		typ = @symbol(operationStartedSignal);
+		break;
 #endif
 #ifdef WSAEALREADY
-            case WSAEALREADY:
-                sym = @symbol(WSAEALREADY);
-                typ = @symbol(operationStartedSignal);
-                break;
+	    case WSAEALREADY:
+		sym = @symbol(WSAEALREADY);
+		typ = @symbol(operationStartedSignal);
+		break;
 #endif
 #ifdef WSAENOTSOCK
-            case WSAENOTSOCK:
-                sym = @symbol(WSAENOTSOCK);
-                typ = @symbol(inappropriateOperationSignal);
-                break;
+	    case WSAENOTSOCK:
+		sym = @symbol(WSAENOTSOCK);
+		typ = @symbol(inappropriateOperationSignal);
+		break;
 #endif
 #ifdef WSAEPROTONOSUPPORT
-            case WSAEPROTONOSUPPORT:
-                sym = @symbol(WSAEPROTONOSUPPORT);
-                typ = @symbol(unsupportedOperationSignal);
-                break;
+	    case WSAEPROTONOSUPPORT:
+		sym = @symbol(WSAEPROTONOSUPPORT);
+		typ = @symbol(unsupportedOperationSignal);
+		break;
 #endif
 #ifdef WSAESOCKTNOSUPPORT
-            case WSAESOCKTNOSUPPORT:
-                sym = @symbol(WSAESOCKTNOSUPPORT);
-                typ = @symbol(unsupportedOperationSignal);
-                break;
+	    case WSAESOCKTNOSUPPORT:
+		sym = @symbol(WSAESOCKTNOSUPPORT);
+		typ = @symbol(unsupportedOperationSignal);
+		break;
 #endif
 #ifdef E_NOINTERFACE
-            case E_NOINTERFACE:
-                sym = @symbol(E_NOINTERFACE);
-                typ = @symbol(noInterfaceSignal);
-                break;
+	    case E_NOINTERFACE:
+		sym = @symbol(E_NOINTERFACE);
+		typ = @symbol(noInterfaceSignal);
+		break;
 #endif
 #ifdef CO_E_NOTINITIALIZED
-            case CO_E_NOTINITIALIZED:
-                sym = @symbol(CO_E_NOTINITIALIZED);
-                typ = @symbol(coNotInitializedSignal);
-                break;
+	    case CO_E_NOTINITIALIZED:
+		sym = @symbol(CO_E_NOTINITIALIZED);
+		typ = @symbol(coNotInitializedSignal);
+		break;
 #endif
 #ifdef REGDB_E_CLASSNOTREG
-            case REGDB_E_CLASSNOTREG:
-                sym = @symbol(REGDB_E_CLASSNOTREG);
-                typ = @symbol(classNotRegisteredSignal);
-                break;
+	    case REGDB_E_CLASSNOTREG:
+		sym = @symbol(REGDB_E_CLASSNOTREG);
+		typ = @symbol(classNotRegisteredSignal);
+		break;
 #endif
 #ifdef CLASS_E_NOAGGREGATION
-            case CLASS_E_NOAGGREGATION:
-                sym = @symbol(CLASS_E_NOAGGREGATION);
-                typ = @symbol(noAggregationSignal);
-                break;
+	    case CLASS_E_NOAGGREGATION:
+		sym = @symbol(CLASS_E_NOAGGREGATION);
+		typ = @symbol(noAggregationSignal);
+		break;
 #endif
 #ifdef DISP_E_UNKNOWNNAME
-            case DISP_E_UNKNOWNNAME:
-                sym = @symbol(DISP_E_UNKNOWNNAME);
-                typ = @symbol(unknownNameSignal);
-                break;
+	    case DISP_E_UNKNOWNNAME:
+		sym = @symbol(DISP_E_UNKNOWNNAME);
+		typ = @symbol(unknownNameSignal);
+		break;
 #endif
 #ifdef OLEOBJ_E_NOVERBS
-            case OLEOBJ_E_NOVERBS:
-                sym = @symbol(OLEOBJ_E_NOVERBS);
-                typ = @symbol(noVerbsSignal);
-                break;
-#endif
-
-            default:
-                break;
-        }
+	    case OLEOBJ_E_NOVERBS:
+		sym = @symbol(OLEOBJ_E_NOVERBS);
+		typ = @symbol(noVerbsSignal);
+		break;
+#endif
+
+	    default:
+		break;
+	}
       }
     }
 %}.
     holder := OSErrorHolder new.
     sym isNil ifTrue:[
-        sym := #ERROR_OTHER.
-        errNr notNil ifTrue:[
-            "keep symbols as symbols"
-            holder parameter:(errNr isString ifTrue:[errNr] ifFalse:[errNr asString]).
-        ].
+	sym := #ERROR_OTHER.
+	errNr notNil ifTrue:[
+	    "keep symbols as symbols"
+	    holder parameter:(errNr isString ifTrue:[errNr] ifFalse:[errNr asString]).
+	].
     ].
     holder errorSymbol:sym errorCategory:(typ ? #defaultOsErrorSignal).
     ^ holder
@@ -2752,212 +2753,212 @@
      */
 #ifdef ERROR_INVALID_FUNCTION
     if (sym == @symbol(ERROR_INVALID_FUNCTION)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_FUNCTION)) );
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_FUNCTION)) );
     }
 #endif
 #ifdef ERROR_BAD_FORMAT
     if (sym == @symbol(ERROR_BAD_FORMAT)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_BAD_FORMAT)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_BAD_FORMAT)));
     }
 #endif
 #ifdef ERROR_FILE_NOT_FOUND
     if (sym == @symbol(ERROR_FILE_NOT_FOUND)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_FILE_NOT_FOUND)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_FILE_NOT_FOUND)));
     }
 #endif
 #ifdef ERROR_PATH_NOT_FOUND
     if (sym == @symbol(ERROR_PATH_NOT_FOUND)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_PATH_NOT_FOUND)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_PATH_NOT_FOUND)));
     }
 #endif
 #ifdef ERROR_TOO_MANY_OPEN_FILES
     if (sym == @symbol(ERROR_TOO_MANY_OPEN_FILES)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_TOO_MANY_OPEN_FILES)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_TOO_MANY_OPEN_FILES)));
     }
 #endif
 #ifdef ERROR_OPEN_FAILED
     if (sym == @symbol(ERROR_OPEN_FAILED)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_OPEN_FAILED)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_OPEN_FAILED)));
     }
 #endif
 #ifdef ERROR_ACCESS_DENIED
     if (sym == @symbol(ERROR_ACCESS_DENIED)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_ACCESS_DENIED)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_ACCESS_DENIED)));
     }
 #endif
 #ifdef ERROR_INVALID_HANDLE
     if (sym == @symbol(ERROR_INVALID_HANDLE)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_HANDLE)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_HANDLE)));
     }
 #endif
 #ifdef ERROR_NOT_ENOUGH_MEMORY
     if (sym == @symbol(ERROR_NOT_ENOUGH_MEMORY)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NOT_ENOUGH_MEMORY)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NOT_ENOUGH_MEMORY)));
     }
 #endif
 #ifdef ERROR_NO_SYSTEM_RESOURCES
     if (sym == @symbol(ERROR_NO_SYSTEM_RESOURCES)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NO_SYSTEM_RESOURCES)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NO_SYSTEM_RESOURCES)));
     }
 #endif
 #ifdef ERROR_INVALID_ACCESS
     if (sym == @symbol(ERROR_INVALID_ACCESS)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_ACCESS)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_ACCESS)));
     }
 #endif
 #ifdef ERROR_INVALID_DATA
     if (sym == @symbol(ERROR_INVALID_DATA)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_DATA)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_DATA)));
     }
 #endif
 #ifdef ERROR_INVALID_NAME
     if (sym == @symbol(ERROR_INVALID_NAME)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_NAME)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_NAME)));
     }
 #endif
 #ifdef ERROR_ARENA_TRASHED
     if (sym == @symbol(ERROR_ARENA_TRASHED)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_ARENA_TRASHED)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_ARENA_TRASHED)));
     }
 #endif
 #ifdef ERROR_OUTOFMEMORY
     if (sym == @symbol(ERROR_OUTOFMEMORY)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_OUTOFMEMORY)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_OUTOFMEMORY)));
     }
 #endif
 #ifdef ERROR_BROKEN_PIPE
     if (sym == @symbol(ERROR_BROKEN_PIPE)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_BROKEN_PIPE)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_BROKEN_PIPE)));
     }
 #endif
 #ifdef ERROR_GEN_FAILURE
     if (sym == @symbol(ERROR_GEN_FAILURE)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_GEN_FAILURE)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_GEN_FAILURE)));
     }
 #endif
 #ifdef ERROR_WRITE_PROTECT
     if (sym == @symbol(ERROR_WRITE_PROTECT)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_WRITE_PROTECT)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_WRITE_PROTECT)));
     }
 #endif
 #ifdef ERROR_WRITE_FAULT
     if (sym == @symbol(ERROR_WRITE_FAULT)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_WRITE_FAULT)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_WRITE_FAULT)));
     }
 #endif
 #ifdef ERROR_READ_FAULT
     if (sym == @symbol(ERROR_READ_FAULT)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_READ_FAULT)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_READ_FAULT)));
     }
 #endif
 #ifdef ERROR_HANDLE_DISK_FULL
     if (sym == @symbol(ERROR_HANDLE_DISK_FULL)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_HANDLE_DISK_FULL)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_HANDLE_DISK_FULL)));
     }
 #endif
 #ifdef ERROR_DISK_FULL
     if (sym == @symbol(ERROR_DISK_FULL)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_DISK_FULL)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_DISK_FULL)));
     }
 #endif
 #ifdef ERROR_ERROR_SHARING_VIOLATION
     if (sym == @symbol(ERROR_ERROR_SHARING_VIOLATION)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_ERROR_SHARING_VIOLATION)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_ERROR_SHARING_VIOLATION)));
     }
 #endif
 #ifdef ERROR_LOCK_VIOLATION
     if (sym == @symbol(ERROR_LOCK_VIOLATION)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_LOCK_VIOLATION)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_LOCK_VIOLATION)));
     }
 #endif
 #ifdef ERROR_INVALID_PARAMETER
     if (sym == @symbol(ERROR_INVALID_PARAMETER)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_PARAMETER)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_PARAMETER)));
     }
 #endif
 #ifdef ERROR_NET_WRITE_FAULT
     if (sym == @symbol(ERROR_NET_WRITE_FAULT)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NET_WRITE_FAULT)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NET_WRITE_FAULT)));
     }
 #endif
 #ifdef ERROR_NOT_SUPPORTED
     if (sym == @symbol(ERROR_NOT_SUPPORTED)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NOT_SUPPORTED)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NOT_SUPPORTED)));
     }
 #endif
 #ifdef ERROR_REM_NOT_LIST
     if (sym == @symbol(ERROR_REM_NOT_LIST)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_REM_NOT_LIST)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_REM_NOT_LIST)));
     }
 #endif
 #ifdef ERROR_NETWORK_ACCESS_DENIED
     if (sym == @symbol(ERROR_NETWORK_ACCESS_DENIED)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NETWORK_ACCESS_DENIED)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NETWORK_ACCESS_DENIED)));
     }
 #endif
 #ifdef ERROR_DUP_NAME
     if (sym == @symbol(ERROR_DUP_NAME)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_DUP_NAME)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_DUP_NAME)));
     }
 #endif
 #ifdef ERROR_BAD_NETPATH
     if (sym == @symbol(ERROR_BAD_NETPATH)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_BAD_NETPATH)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_BAD_NETPATH)));
     }
 #endif
 #ifdef ERROR_NETWORK_BUSY
     if (sym == @symbol(ERROR_NETWORK_BUSY)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NETWORK_BUSY)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NETWORK_BUSY)));
     }
 #endif
 #ifdef ERROR_DRIVE_LOCKED
     if (sym == @symbol(ERROR_DRIVE_LOCKED)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_DRIVE_LOCKED)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_DRIVE_LOCKED)));
     }
 #endif
 #ifdef ERROR_INVALID_DRIVE
     if (sym == @symbol(ERROR_INVALID_DRIVE)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_DRIVE)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_INVALID_DRIVE)));
     }
 #endif
 #ifdef ERROR_WRONG_DISK
     if (sym == @symbol(ERROR_WRONG_DISK)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_WRONG_DISK)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_WRONG_DISK)));
     }
 #endif
 #ifdef ERROR_CURRENT_DIRECTORY
     if (sym == @symbol(ERROR_CURRENT_DIRECTORY)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_CURRENT_DIRECTORY)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_CURRENT_DIRECTORY)));
     }
 #endif
 #ifdef ERROR_CANNOT_MAKE
     if (sym == @symbol(ERROR_CANNOT_MAKE)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_CANNOT_MAKE)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_CANNOT_MAKE)));
     }
 #endif
 #ifdef ERROR_NO_MORE_FILES
     if (sym == @symbol(ERROR_NO_MORE_FILES)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NO_MORE_FILES)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NO_MORE_FILES)));
     }
 #endif
 #ifdef ERROR_NOT_READY
     if (sym == @symbol(ERROR_NOT_READY)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NOT_READY)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NOT_READY)));
     }
 #endif
 #ifdef ERROR_NOT_DOS_DISK
     if (sym == @symbol(ERROR_NOT_DOS_DISK)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NOT_DOS_DISK)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_NOT_DOS_DISK)));
     }
 #endif
 #ifdef ERROR_OUT_OF_PAPER
     if (sym == @symbol(ERROR_OUT_OF_PAPER)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_OUT_OF_PAPER)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_OUT_OF_PAPER)));
     }
 #endif
 #ifdef ERROR_PRINTQ_FULL
     if (sym == @symbol(ERROR_PRINTQ_FULL)) {
-        RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_PRINTQ_FULL)));
+	RETURN ( __mkSmallInteger(__WIN32_ERR(ERROR_PRINTQ_FULL)));
     }
 #endif
 
@@ -2966,229 +2967,229 @@
      */
 #ifdef EPERM
     if (sym == @symbol(EPERM)) {
-        RETURN ( __mkSmallInteger(EPERM) );
+	RETURN ( __mkSmallInteger(EPERM) );
     }
 #endif
 
 #ifdef ENOENT
     if (sym == @symbol(ENOENT)) {
-        RETURN ( __mkSmallInteger(ENOENT) );
+	RETURN ( __mkSmallInteger(ENOENT) );
     }
 #endif
 
 #ifdef ESRCH
     if (sym == @symbol(ESRCH)) {
-        RETURN ( __mkSmallInteger(ESRCH) );
+	RETURN ( __mkSmallInteger(ESRCH) );
     }
 #endif
 
 #ifdef EINTR
     if (sym == @symbol(EINTR)) {
-        RETURN ( __mkSmallInteger(EINTR) );
+	RETURN ( __mkSmallInteger(EINTR) );
     }
 #endif
 
 #ifdef EIO
     if (sym == @symbol(EIO)) {
-        RETURN ( __mkSmallInteger(EIO) );
+	RETURN ( __mkSmallInteger(EIO) );
     }
 #endif
 
 #ifdef ENXIO
     if (sym == @symbol(ENXIO)) {
-        RETURN ( __mkSmallInteger(ENXIO) );
+	RETURN ( __mkSmallInteger(ENXIO) );
     }
 #endif
 
 #ifdef E2BIG
     if (sym == @symbol(E2BIG)) {
-        RETURN ( __mkSmallInteger(E2BIG) );
+	RETURN ( __mkSmallInteger(E2BIG) );
     }
 #endif
 
 #ifdef ENOEXEC
     if (sym == @symbol(ENOEXEC)) {
-        RETURN ( __mkSmallInteger(ENOEXEC) );
+	RETURN ( __mkSmallInteger(ENOEXEC) );
     }
 #endif
 
 #ifdef EBADF
     if (sym == @symbol(EBADF)) {
-        RETURN ( __mkSmallInteger(EBADF) );
+	RETURN ( __mkSmallInteger(EBADF) );
     }
 #endif
 
 #ifdef ECHILD
     if (sym == @symbol(ECHILD)) {
-        RETURN ( __mkSmallInteger(ECHILD) );
+	RETURN ( __mkSmallInteger(ECHILD) );
     }
 #endif
 
 #if defined(EAGAIN)
     if (sym == @symbol(EAGAIN)) {
-        RETURN ( __mkSmallInteger(EAGAIN) );
+	RETURN ( __mkSmallInteger(EAGAIN) );
     }
 #endif
 
 #ifdef ENOMEM
     if (sym == @symbol(ENOMEM)) {
-        RETURN ( __mkSmallInteger(ENOMEM) );
+	RETURN ( __mkSmallInteger(ENOMEM) );
     }
 #endif
 
 #ifdef EACCES
     if (sym == @symbol(EACCES)) {
-        RETURN ( __mkSmallInteger(EACCES) );
+	RETURN ( __mkSmallInteger(EACCES) );
     }
 #endif
 
 #ifdef EFAULT
     if (sym == @symbol(EFAULT)) {
-        RETURN ( __mkSmallInteger(EFAULT) );
+	RETURN ( __mkSmallInteger(EFAULT) );
     }
 #endif
 
 #ifdef EBUSY
     if (sym == @symbol(EBUSY)) {
-        RETURN ( __mkSmallInteger(EBUSY) );
+	RETURN ( __mkSmallInteger(EBUSY) );
     }
 #endif
 
 #ifdef EXDEV
     if (sym == @symbol(EXDEV)) {
-        RETURN ( __mkSmallInteger(EXDEV) );
+	RETURN ( __mkSmallInteger(EXDEV) );
     }
 #endif
 
 #ifdef ENODEV
     if (sym == @symbol(ENODEV)) {
-        RETURN ( __mkSmallInteger(ENODEV) );
+	RETURN ( __mkSmallInteger(ENODEV) );
     }
 #endif
 
 #ifdef ENOTDIR
     if (sym == @symbol(ENOTDIR)) {
-        RETURN ( __mkSmallInteger(ENOTDIR) );
+	RETURN ( __mkSmallInteger(ENOTDIR) );
     }
 #endif
 
 #ifdef EISDIR
     if (sym == @symbol(EISDIR)) {
-        RETURN ( __mkSmallInteger(EISDIR) );
+	RETURN ( __mkSmallInteger(EISDIR) );
     }
 #endif
 
 #ifdef EINVAL
     if (sym == @symbol(EINVAL)) {
-        RETURN ( __mkSmallInteger(EINVAL) );
+	RETURN ( __mkSmallInteger(EINVAL) );
     }
 #endif
 
 #ifdef ENFILE
     if (sym == @symbol(ENFILE)) {
-        RETURN ( __mkSmallInteger(ENFILE) );
+	RETURN ( __mkSmallInteger(ENFILE) );
     }
 #endif
 
 #ifdef EMFILE
     if (sym == @symbol(EMFILE)) {
-        RETURN ( __mkSmallInteger(EMFILE) );
+	RETURN ( __mkSmallInteger(EMFILE) );
     }
 #endif
 
 #ifdef ENOTTY
     if (sym == @symbol(ENOTTY)) {
-        RETURN ( __mkSmallInteger(ENOTTY) );
+	RETURN ( __mkSmallInteger(ENOTTY) );
     }
 #endif
 
 #ifdef EFBIG
     if (sym == @symbol(EFBIG)) {
-        RETURN ( __mkSmallInteger(EFBIG) );
+	RETURN ( __mkSmallInteger(EFBIG) );
     }
 #endif
 
 #ifdef ENOSPC
     if (sym == @symbol(ENOSPC)) {
-        RETURN ( __mkSmallInteger(ENOSPC) );
+	RETURN ( __mkSmallInteger(ENOSPC) );
     }
 #endif
 
 #ifdef ESPIPE
     if (sym == @symbol(ESPIPE)) {
-        RETURN ( __mkSmallInteger(ESPIPE) );
+	RETURN ( __mkSmallInteger(ESPIPE) );
     }
 #endif
 
 #ifdef EROFS
     if (sym == @symbol(EROFS)) {
-        RETURN ( __mkSmallInteger(EROFS) );
+	RETURN ( __mkSmallInteger(EROFS) );
     }
 #endif
 
 #ifdef EMLINK
     if (sym == @symbol(EMLINK)) {
-        RETURN ( __mkSmallInteger(EMLINK) );
+	RETURN ( __mkSmallInteger(EMLINK) );
     }
 #endif
 
 #ifdef EPIPE
     if (sym == @symbol(EPIPE)) {
-        RETURN ( __mkSmallInteger(EPIPE) );
+	RETURN ( __mkSmallInteger(EPIPE) );
     }
 #endif
 
 #ifdef EDOM
     if (sym == @symbol(EDOM)) {
-        RETURN ( __mkSmallInteger(EDOM) );
+	RETURN ( __mkSmallInteger(EDOM) );
     }
 #endif
 
 #ifdef ERANGE
     if (sym == @symbol(ERANGE)) {
-        RETURN ( __mkSmallInteger(ERANGE) );
+	RETURN ( __mkSmallInteger(ERANGE) );
     }
 #endif
 
 #ifdef EDEADLK
     if (sym == @symbol(EDEADLK)) {
-        RETURN ( __mkSmallInteger(EDEADLK) );
+	RETURN ( __mkSmallInteger(EDEADLK) );
     }
 #endif
 
 #ifdef ENAMETOOLONG
     if (sym == @symbol(ENAMETOOLONG)) {
-        RETURN ( __mkSmallInteger(ENAMETOOLONG) );
+	RETURN ( __mkSmallInteger(ENAMETOOLONG) );
     }
 #endif
 
 #ifdef ENOLCK
     if (sym == @symbol(ENOLCK)) {
-        RETURN ( __mkSmallInteger(ENOLCK) );
+	RETURN ( __mkSmallInteger(ENOLCK) );
     }
 #endif
 
 #ifdef ENOSYS
     if (sym == @symbol(ENOSYS)) {
-        RETURN ( __mkSmallInteger(ENOSYS) );
+	RETURN ( __mkSmallInteger(ENOSYS) );
     }
 #endif
 
 #ifdef ENOTEMPTY
     if (sym == @symbol(ENOTEMPTY)) {
-        RETURN ( __mkSmallInteger(ENOTEMPTY) );
+	RETURN ( __mkSmallInteger(ENOTEMPTY) );
     }
 #endif
 
 #ifdef EEXIST
     if (sym == @symbol(EEXIST)) {
-        RETURN ( __mkSmallInteger(EEXIST) );
+	RETURN ( __mkSmallInteger(EEXIST) );
     }
 #endif
 
 #ifdef EILSEQ
     if (sym == @symbol(EILSEQ)) {
-        RETURN ( __mkSmallInteger(EILSEQ) );
+	RETURN ( __mkSmallInteger(EILSEQ) );
     }
 #endif
 
@@ -3197,13 +3198,13 @@
      */
 #ifdef ENOTBLK
     if (sym == @symbol(ENOTBLK)) {
-        RETURN ( __mkSmallInteger(ENOTBLK) );
+	RETURN ( __mkSmallInteger(ENOTBLK) );
     }
 #endif
 
 #ifdef ETXTBSY
     if (sym == @symbol(ETXTBSY)) {
-        RETURN ( __mkSmallInteger(ETXTBSY) );
+	RETURN ( __mkSmallInteger(ETXTBSY) );
     }
 #endif
 
@@ -3212,19 +3213,19 @@
      */
 #ifdef EWOULDBLOCK
     if (sym == @symbol(EWOULDBLOCK)) {
-        RETURN ( __mkSmallInteger(EWOULDBLOCK) );
+	RETURN ( __mkSmallInteger(EWOULDBLOCK) );
     }
 #endif
 
 #ifdef ENOMSG
     if (sym == @symbol(ENOMSG)) {
-        RETURN ( __mkSmallInteger(ENOMSG) );
+	RETURN ( __mkSmallInteger(ENOMSG) );
     }
 #endif
 
 #ifdef ELOOP
     if (sym == @symbol(ELOOP)) {
-        RETURN ( __mkSmallInteger(ELOOP) );
+	RETURN ( __mkSmallInteger(ELOOP) );
     }
 #endif
 
@@ -3233,31 +3234,31 @@
      */
 #ifdef ETIME
     if (sym == @symbol(ETIME)) {
-        RETURN ( __mkSmallInteger(ETIME) );
+	RETURN ( __mkSmallInteger(ETIME) );
     }
 #endif
 
 #ifdef ENOSR
     if (sym == @symbol(ENOSR)) {
-        RETURN ( __mkSmallInteger(ENOSR) );
+	RETURN ( __mkSmallInteger(ENOSR) );
     }
 #endif
 
 #ifdef ENOSTR
     if (sym == @symbol(ENOSTR)) {
-        RETURN ( __mkSmallInteger(ENOSTR) );
+	RETURN ( __mkSmallInteger(ENOSTR) );
     }
 #endif
 
 #ifdef ECOMM
     if (sym == @symbol(ECOMM)) {
-        RETURN ( __mkSmallInteger(ECOMM) );
+	RETURN ( __mkSmallInteger(ECOMM) );
     }
 #endif
 
 #ifdef EPROTO
     if (sym == @symbol(EPROTO)) {
-        RETURN ( __mkSmallInteger(EPROTO) );
+	RETURN ( __mkSmallInteger(EPROTO) );
     }
 #endif
 
@@ -3266,13 +3267,13 @@
      */
 #ifdef ESTALE
     if (sym == @symbol(ESTALE)) {
-        RETURN ( __mkSmallInteger(ESTALE) );
+	RETURN ( __mkSmallInteger(ESTALE) );
     }
 #endif
 
 #ifdef EREMOTE
     if (sym == @symbol(EREMOTE)) {
-        RETURN ( __mkSmallInteger(EREMOTE) );
+	RETURN ( __mkSmallInteger(EREMOTE) );
     }
 #endif
 
@@ -3281,162 +3282,162 @@
      */
 #ifdef EINPROGRESS
     if (sym == @symbol(EINPROGRESS)) {
-        RETURN ( __mkSmallInteger(EINPROGRESS) );
+	RETURN ( __mkSmallInteger(EINPROGRESS) );
     }
 #endif
 
 #ifdef EALREADY
     if (sym == @symbol(EALREADY)) {
-        RETURN ( __mkSmallInteger(EALREADY) );
+	RETURN ( __mkSmallInteger(EALREADY) );
     }
 #endif
 
 #ifdef ENOTSOCK
     if (sym == @symbol(ENOTSOCK)) {
-        RETURN ( __mkSmallInteger(ENOTSOCK) );
+	RETURN ( __mkSmallInteger(ENOTSOCK) );
     }
 #endif
 
 #ifdef EDESTADDRREQ
     if (sym == @symbol(EDESTADDRREQ)) {
-        RETURN ( __mkSmallInteger(EDESTADDRREQ) );
+	RETURN ( __mkSmallInteger(EDESTADDRREQ) );
     }
 #endif
 
 #ifdef EMSGSIZE
     if (sym == @symbol(EMSGSIZE)) {
-        RETURN ( __mkSmallInteger(EMSGSIZE) );
+	RETURN ( __mkSmallInteger(EMSGSIZE) );
     }
 #endif
 
 #ifdef EPROTOTYPE
     if (sym == @symbol(EPROTOTYPE)) {
-        RETURN ( __mkSmallInteger(EPROTOTYPE) );
+	RETURN ( __mkSmallInteger(EPROTOTYPE) );
     }
 #endif
 
 #ifdef ENOPROTOOPT
     if (sym == @symbol(ENOPROTOOPT)) {
-        RETURN ( __mkSmallInteger(ENOPROTOOPT) );
+	RETURN ( __mkSmallInteger(ENOPROTOOPT) );
     }
 #endif
 
 #ifdef EPROTONOSUPPORT
     if (sym == @symbol(EPROTONOSUPPORT)) {
-        RETURN ( __mkSmallInteger(EPROTONOSUPPORT) );
+	RETURN ( __mkSmallInteger(EPROTONOSUPPORT) );
     }
 #endif
 
 #ifdef ESOCKTNOSUPPORT
     if (sym == @symbol(ESOCKTNOSUPPORT)) {
-        RETURN ( __mkSmallInteger(ESOCKTNOSUPPORT) );
+	RETURN ( __mkSmallInteger(ESOCKTNOSUPPORT) );
     }
 #endif
 
 #ifdef EOPNOTSUPP
     if (sym == @symbol(EOPNOTSUPP)) {
-        RETURN ( __mkSmallInteger(EOPNOTSUPP) );
+	RETURN ( __mkSmallInteger(EOPNOTSUPP) );
     }
 #endif
 
 #ifdef EPFNOSUPPORT
     if (sym == @symbol(EPFNOSUPPORT)) {
-        RETURN ( __mkSmallInteger(EPFNOSUPPORT) );
+	RETURN ( __mkSmallInteger(EPFNOSUPPORT) );
     }
 #endif
 
 #ifdef EAFNOSUPPORT
     if (sym == @symbol(EAFNOSUPPORT)) {
-        RETURN ( __mkSmallInteger(EAFNOSUPPORT) );
+	RETURN ( __mkSmallInteger(EAFNOSUPPORT) );
     }
 #endif
 
 #ifdef EADDRINUSE
     if (sym == @symbol(EADDRINUSE)) {
-        RETURN ( __mkSmallInteger(EADDRINUSE) );
+	RETURN ( __mkSmallInteger(EADDRINUSE) );
     }
 #endif
 
 #ifdef EADDRNOTAVAIL
     if (sym == @symbol(EADDRNOTAVAIL)) {
-        RETURN ( __mkSmallInteger(EADDRNOTAVAIL) );
+	RETURN ( __mkSmallInteger(EADDRNOTAVAIL) );
     }
 #endif
 
 #ifdef ETIMEDOUT
     if (sym == @symbol(ETIMEDOUT)) {
-        RETURN ( __mkSmallInteger(ETIMEDOUT) );
+	RETURN ( __mkSmallInteger(ETIMEDOUT) );
     }
 #endif
 #ifdef WSAETIMEDOUT
     if (sym == @symbol(ETIMEDOUT)) {
-        RETURN ( __mkSmallInteger(WSAETIMEDOUT) );
+	RETURN ( __mkSmallInteger(WSAETIMEDOUT) );
     }
 #endif
 
 #ifdef ECONNREFUSED
     if (sym == @symbol(ECONNREFUSED)) {
-        RETURN ( __mkSmallInteger(ECONNREFUSED) );
+	RETURN ( __mkSmallInteger(ECONNREFUSED) );
     }
 #endif
 
 #ifdef ENETDOWN
     if (sym == @symbol(ENETDOWN)) {
-        RETURN ( __mkSmallInteger(ENETDOWN) );
+	RETURN ( __mkSmallInteger(ENETDOWN) );
     }
 #endif
 
 #ifdef ENETUNREACH
     if (sym == @symbol(ENETUNREACH)) {
-        RETURN ( __mkSmallInteger(ENETUNREACH) );
+	RETURN ( __mkSmallInteger(ENETUNREACH) );
     }
 #endif
 
 #ifdef ENETRESET
     if (sym == @symbol(ENETRESET)) {
-        RETURN ( __mkSmallInteger(ENETRESET) );
+	RETURN ( __mkSmallInteger(ENETRESET) );
     }
 #endif
 
 #ifdef ECONNABORTED
     if (sym == @symbol(ECONNABORTED)) {
-        RETURN ( __mkSmallInteger(ECONNABORTED) );
+	RETURN ( __mkSmallInteger(ECONNABORTED) );
     }
 #endif
 
 #ifdef ECONNRESET
     if (sym == @symbol(ECONNRESET)) {
-        RETURN ( __mkSmallInteger(ECONNRESET) );
+	RETURN ( __mkSmallInteger(ECONNRESET) );
     }
 #endif
 
 #ifdef EISCONN
     if (sym == @symbol(EISCONN)) {
-        RETURN ( __mkSmallInteger(EISCONN) );
+	RETURN ( __mkSmallInteger(EISCONN) );
     }
 #endif
 
 #ifdef ENOTCONN
     if (sym == @symbol(ENOTCONN)) {
-        RETURN ( __mkSmallInteger(ENOTCONN) );
+	RETURN ( __mkSmallInteger(ENOTCONN) );
     }
 #endif
 
 #ifdef ESHUTDOWN
     if (sym == @symbol(ESHUTDOWN)) {
-        RETURN ( __mkSmallInteger(ESHUTDOWN) );
+	RETURN ( __mkSmallInteger(ESHUTDOWN) );
     }
 #endif
 
 #ifdef EHOSTDOWN
     if (sym == @symbol(EHOSTDOWN)) {
-        RETURN ( __mkSmallInteger(EHOSTDOWN) );
+	RETURN ( __mkSmallInteger(EHOSTDOWN) );
     }
 #endif
 
 #ifdef EHOSTUNREACH
     if (sym == @symbol(EHOSTUNREACH)) {
-        RETURN ( __mkSmallInteger(EHOSTUNREACH) );
+	RETURN ( __mkSmallInteger(EHOSTUNREACH) );
     }
 #endif
     /*
@@ -3444,92 +3445,92 @@
      */
 #ifdef WSAEINTR
     if (sym == @symbol(WSAEINTR)) {
-        RETURN ( __mkSmallInteger(WSAEINTR) );
+	RETURN ( __mkSmallInteger(WSAEINTR) );
     }
 #endif
 #ifdef WSAEBADF
     if (sym == @symbol(WSAEBADF)) {
-        RETURN ( __mkSmallInteger(WSAEBADF) );
+	RETURN ( __mkSmallInteger(WSAEBADF) );
     }
 #endif
 #ifdef WSAEACCESS
     if (sym == @symbol(WSAEACCESS)) {
-        RETURN ( __mkSmallInteger(WSAEACCESS) );
+	RETURN ( __mkSmallInteger(WSAEACCESS) );
     }
 #endif
 #ifdef WSAEFAULT
     if (sym == @symbol(WSAEFAULT)) {
-        RETURN ( __mkSmallInteger(WSAEFAULT) );
+	RETURN ( __mkSmallInteger(WSAEFAULT) );
     }
 #endif
 #ifdef WSAEINVAL
     if (sym == @symbol(WSAEINVAL)) {
-        RETURN ( __mkSmallInteger(WSAEINVAL) );
+	RETURN ( __mkSmallInteger(WSAEINVAL) );
     }
 #endif
 #ifdef WSAEMFILE
     if (sym == @symbol(WSAEMFILE)) {
-        RETURN ( __mkSmallInteger(WSAEMFILE) );
+	RETURN ( __mkSmallInteger(WSAEMFILE) );
     }
 #endif
 #ifdef WSAEWOULDBLOCK
     if (sym == @symbol(WSAEWOULDBLOCK)) {
-        RETURN ( __mkSmallInteger(WSAEWOULDBLOCK) );
+	RETURN ( __mkSmallInteger(WSAEWOULDBLOCK) );
     }
 #endif
 #ifdef WSAEINPROGRESS
     if (sym == @symbol(WSAEINPROGRESS)) {
-        RETURN ( __mkSmallInteger(WSAEINPROGRESS) );
+	RETURN ( __mkSmallInteger(WSAEINPROGRESS) );
     }
 #endif
 #ifdef WSAEALREADY
     if (sym == @symbol(WSAEALREADY)) {
-        RETURN ( __mkSmallInteger(WSAEALREADY) );
+	RETURN ( __mkSmallInteger(WSAEALREADY) );
     }
 #endif
 #ifdef WSAENOTSOCK
     if (sym == @symbol(WSAENOTSOCK)) {
-        RETURN ( __mkSmallInteger(WSAENOTSOCK) );
+	RETURN ( __mkSmallInteger(WSAENOTSOCK) );
     }
 #endif
 #ifdef WSAEPROTONOSUPPORT
     if (sym == @symbol(WSAEPROTONOSUPPORT)) {
-        RETURN ( __mkSmallInteger(WSAEPROTONOSUPPORT) );
+	RETURN ( __mkSmallInteger(WSAEPROTONOSUPPORT) );
     }
 #endif
 #ifdef WSAESOCKTNOSUPPORT
     if (sym == @symbol(WSAESOCKTNOSUPPORT)) {
-        RETURN ( __mkSmallInteger(WSAESOCKTNOSUPPORT) );
+	RETURN ( __mkSmallInteger(WSAESOCKTNOSUPPORT) );
     }
 #endif
 #ifdef E_NOINTERFACE
     if (sym == @symbol(E_NOINTERFACE)) {
-        RETURN ( __MKUINT(E_NOINTERFACE) );
+	RETURN ( __MKUINT(E_NOINTERFACE) );
     }
 #endif
 #ifdef CO_E_NOTINITIALIZED
     if (sym == @symbol(CO_E_NOTINITIALIZED)) {
-        RETURN ( __MKUINT(CO_E_NOTINITIALIZED) );
+	RETURN ( __MKUINT(CO_E_NOTINITIALIZED) );
     }
 #endif
 #ifdef REGDB_E_CLASSNOTREG
     if (sym == @symbol(REGDB_E_CLASSNOTREG)) {
-        RETURN ( __MKUINT(REGDB_E_CLASSNOTREG) );
+	RETURN ( __MKUINT(REGDB_E_CLASSNOTREG) );
     }
 #endif
 #ifdef CLASS_E_NOAGGREGATION
     if (sym == @symbol(CLASS_E_NOAGGREGATION)) {
-        RETURN ( __MKUINT(CLASS_E_NOAGGREGATION) );
+	RETURN ( __MKUINT(CLASS_E_NOAGGREGATION) );
     }
 #endif
 #ifdef DISP_E_UNKNOWNNAME
     if (sym == @symbol(DISP_E_UNKNOWNNAME)) {
-        RETURN ( __MKUINT(DISP_E_UNKNOWNNAME) );
+	RETURN ( __MKUINT(DISP_E_UNKNOWNNAME) );
     }
 #endif
 #ifdef OLEOBJ_E_NOVERBS
     if (sym == @symbol(OLEOBJ_E_NOVERBS)) {
-        RETURN ( __MKUINT(OLEOBJ_E_NOVERBS) );
+	RETURN ( __MKUINT(OLEOBJ_E_NOVERBS) );
     }
 #endif
 
@@ -3565,20 +3566,23 @@
 commandAndArgsForOSCommand:aCommandString
     "get a shell and shell arguments for command execution.
      If aCommandString is a String, the commandString is passed to a shell for execution
-     - see the description of 'sh -c' in your UNIX manual ('cmd.com' in your MSDOS manual).
+     - see the description of 'sh -c' in your UNIX manual ('cmd.exe' in your Windows manual).
      If aCommandString is an Array, the first element is the command to be executed,
-     and the other elements are the arguments to the command. No shell is invoked in this case."
-
-    |shell args wDir cmdName path hasRedirection|
+     and the next elements are the arguments to the command. No shell is invoked in this case.
+     Answer am Array with the command string as the first element,
+     the arguments (a String) as second element,
+     and whether a window should be opened (true, false or nil = let the executed program determine)
+     as third element."
+
+    |shell args wDir cmdName path|
 
     aCommandString isNonByteCollection ifTrue:[
-        "easy: the caller does not want a shell to be executed"
-        ^ Array with:aCommandString first with:(aCommandString asStringWith:' ').
+	"easy: the caller does not want a shell to be executed"
+	^ Array with:aCommandString first with:(aCommandString asStringWith:' ') with:nil.
     ].
 
     "/
-    "/ 'x:\WINNT\System32\cmd /c <command>'
-    "/ or 'x:\WINDOWS\System32\cmd /c <command>'
+    "/ 'x:\WINDOWS\System32\cmd /c <command>'
     "/ or 'x:\WINDOWS\System\cmd /c <command>'
     "/ or whatever ...
     "/
@@ -3589,192 +3593,137 @@
     "/ Here, we see if the command is found along the path and
     "/ call it directly if found.
     "/ If not found, assume its a builtIn or batch command
-    "/ and pass it to command.com.
-    "/ Also use command.com, if any I/O redirection is
+    "/ and pass it to cmd.exe.
+    "/ Also use cmd.exe, if any I/O redirection is
     "/ involved, since that is (not yet) handled here.
     "/
     "/ I know: this is a kludge but should work for now...
     "/ ...this will change in an upcoming version to include
-    "/ command.com command-line parsing here (sigh).
-
-    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.
+    "/ cmd.exe command-line parsing here (sigh).
+
+    cmdName := (aCommandString ? '') withoutSeparators.
+
+    (cmdName isEmpty or:[cmdName includesAny:'<>|']) ifFalse:[
+	"/ test whether the command is a plain executable;
+	"/ if so, no shell is required
+	|index file suffix|
+
+	index := cmdName indexOfSeparatorStartingAt:1.
+	index ~~ 0 ifTrue:[
+	    cmdName := cmdName copyFrom:1 to:(index-1).
+	    args := cmdName copyFrom:(index+1).
+	] ifFalse:[
+	    args := ''.
+	].
+
+	(cmdName first = $" and:[cmdName last = $"]) ifTrue:[
+	    cmdName := (cmdName copyFrom:2 to:cmdName size - 1) withoutSeparators.
+	].
+	file := cmdName asFilename.
+	file suffix isEmpty ifTrue:[
+	    file := file withSuffix:'exe'.
+	].
+	path := file fullAlternativePathName.
+	(OperatingSystem getBinaryType:path) notNil ifTrue:[
+	    "/ is an executable, no shell required
+	    ^ Array with:path with:aCommandString with:nil.
 "/                ^ 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 and:[(OperatingSystem getBinaryType:path) notNil]) ifTrue:[
+	    "/ is an executable, no shell required
+	    ^ Array with:path with:aCommandString with:nil.
 "/                ^ 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.
-    ].
-
-    aCommandString isEmptyOrNil ifTrue:[
-        ^ Array with:shell with:nil
-    ].
-
-    ^ Array with:shell with:(' /c "' , aCommandString, '"')
+	wDir := self getWindowsSystemDirectory asFilename.
+	shell := #('cmd.exe' 'command.com') detect:[:eachCommand|
+			(wDir / eachCommand) isExecutableProgram
+		    ] ifNone:[
+			self error:'no cmd.exe available'.
+		    ].
+	shell := (wDir / shell) pathName.
+    ].
+
+    cmdName isEmpty ifTrue:[
+	^ Array with:shell with:nil with:nil.
+    ].
+
+    ^ Array with:shell with:(' /c "' , aCommandString, '"') with:false.
 
    "
+     self commandAndArgsForOSCommand:''
+     self commandAndArgsForOSCommand:'%ProgramFiles%\notepad++\notepad++.exe'
      self commandAndArgsForOSCommand:'diff'
+     self commandAndArgsForOSCommand:'diff.exe'
      self commandAndArgsForOSCommand:'dir/w'
-     self commandAndArgsForOSCommand:'dir >nul:'
+     self commandAndArgsForOSCommand:'diff >nul:'
+     self commandAndArgsForOSCommand:'diff /bla'
    "
 
     "Modified: / 20-01-1998 / 16:57:19 / md"
     "Modified: / 11-02-2007 / 20:51:08 / cg"
 !
 
-exec:aCommandPath withArguments:argString environment:environment fileDescriptors:fdArray fork:doFork newPgrp:newPgrp inDirectory:aDirectory
+exec:aCommandPath withArguments:argString environment:environment fileDescriptors:fdArray fork:doFork
+	newPgrp:newPgrp inDirectory:aDirectory
+	showWindow:showWindowBooleanOrNil
+
     "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 Win32ProcessHandle of the child process is returned; nil if the fork failed.
+	fork a child to do the above.
+	The Win32ProcessHandle 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
+	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
 
      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.
+
+     showWindowOrBoolean may be:
+	true  - a window is shown on start of the command
+	false - the command window is hidden
+	nil   - the nCmdShown parameter of the commans's winmain function determins,
+		if a window is shown."
 
     |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
-        inheritHandles:true
-        showWindow:false.
-
-"/ 'created ' print. cmdLine print. ' -> ' print. rslt printCR.
-    ^ rslt
-
-    "Modified: / 31.1.1998 / 10:54:24 / md"
-    "Modified: / 15.5.1999 / 18:07:51 / cg"
-!
-
-exec:aCommandPath withArguments:argString environment:environment fileDescriptors:fdArray fork:doFork 
-        newPgrp:newPgrp inDirectory:aDirectory
-        showWindow:showWindowBooleanOrNil
-
-    "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.
-
-     If fork is true (subprocess command execution):
-        fork a child to do the above.
-        The Win32ProcessHandle 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
-
-     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.
-
-     showWindowOrBoolean may be:
-        true  - a window is shown on start of the command
-        false - the command window is hidden
-        nil   - the nCmdShown parameter of the commans's winmain function determins, 
-                if a window is shown."
-
-    |dirPath rslt|
-
-    aDirectory notNil ifTrue:[
-        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
-        inheritHandles:true
-        showWindow:showWindowBooleanOrNil.
+	primExec:aCommandPath
+	commandLine:argString
+	fileDescriptors:fdArray
+	fork:doFork
+	newPgrp:newPgrp
+	inPath:dirPath
+	createFlags:nil
+	inheritHandles:true
+	showWindow:showWindowBooleanOrNil.
 
 "/ 'created ' print. cmdLine print. ' -> ' print. rslt printCR.
     ^ rslt
@@ -3792,28 +3741,28 @@
     INT status = -1;
 
     if (__isExternalAddressLike(aProcessId)) {
-        HANDLE handle = _HANDLEVal(aProcessId);
-        if (handle) {
+	HANDLE handle = _HANDLEVal(aProcessId);
+	if (handle) {
 #ifdef DO_WRAP_CALLS
-            do {
-                __threadErrno = 0;
-                endStatus = (INT)STX_API_CALL2( "WaitForSingleObject", WaitForSingleObject, handle, INFINITE);
-            } while ((endStatus < 0) && (__threadErrno == EINTR));
-#else
-            endStatus = (INT)WaitForSingleObject(handle , INFINITE);
-#endif
-            if (endStatus != WAIT_FAILED) {
-                if (GetExitCodeProcess(handle,&endStatus)) {
-                    status = endStatus;
+	    do {
+		__threadErrno = 0;
+		endStatus = (INT)STX_API_CALL2( "WaitForSingleObject", WaitForSingleObject, handle, INFINITE);
+	    } while ((endStatus < 0) && (__threadErrno == EINTR));
+#else
+	    endStatus = (INT)WaitForSingleObject(handle , INFINITE);
+#endif
+	    if (endStatus != WAIT_FAILED) {
+		if (GetExitCodeProcess(handle,&endStatus)) {
+		    status = endStatus;
 #ifdef PROCESSDEBUGWIN32
-                    console_fprintf(stderr, "getexitcode status = %d\n",status);
-                } else {
-                    console_fprintf(stderr, "getexitcode failed.\n");
-#endif
-                }
-            }
-        }
-        RETURN ( __mkSmallInteger(status));
+		    console_fprintf(stderr, "getexitcode status = %d\n",status);
+		} else {
+		    console_fprintf(stderr, "getexitcode failed.\n");
+#endif
+		}
+	    }
+	}
+	RETURN ( __mkSmallInteger(status));
     }
 %}.
     self primitiveFailed
@@ -3824,13 +3773,13 @@
      return its full pathName if there is such a command, otherwise
      return nil."
 
-    |cmdFile path rentry rpath f fExt|
+    |cmdFile path rentry rpath hasSuffix|
 
     cmdFile := aCommand asFilename.
     cmdFile isAbsolute ifTrue:[
-        cmdFile exists ifTrue:[
-            ^ aCommand
-        ].
+	cmdFile isExecutableProgram ifTrue:[
+	    ^ aCommand
+	].
         cmdFile suffix isEmpty ifTrue:[ 
             ((path := cmdFile withSuffix: 'com') exists 
                 or:[ (path := cmdFile withSuffix: 'exe') exists 
@@ -3840,64 +3789,62 @@
                     ]. 
                 ].
         ].
-        ^ nil
+	^ nil
     ].
 
     (aCommand includes:Filename separator) ifTrue:[
-        path := Filename currentDirectory construct:aCommand.
-        (path exists
-        or:[ (path := path withSuffix:'com') exists
-        or:[ (path := path withSuffix:'exe') exists 
-        or:[ (path := path withSuffix:'bat') exists ]]]) ifTrue:[
-            path isExecutable ifTrue:[
-                ^ path pathName
-            ].
-        ].
-        ^ nil
-    ].
-
+	path := Filename currentDirectory construct:aCommand.
+	path isExecutableProgram ifTrue:[
+	    ^ path pathName.
+	].
+	^ nil
+    ].
+
+    "search in all directories of PATH.
+     If there no extension, add the known extensions."
     path := (self getEnvironment:'PATH') ? ''.
     (rentry := self registryEntry key: 'HKEY_CURRENT_USER\Environment') notNil ifTrue:[
-        rpath := rentry valueNamed: 'PATH'.
-        rpath notNil ifTrue:[
-            path := path , self pathSeparator , rpath
-        ].
-    ].
-    path := '.;',path.
-
-    (path asCollectionOfSubstringsSeparatedBy:(self pathSeparator)) do:[:eachDirectory |
-        eachDirectory isEmpty ifTrue:[
-            f := cmdFile
-        ] ifFalse:[
-            f := eachDirectory asFilename construct:aCommand.
-        ].
-        f suffix isEmpty ifTrue:[
-            self executableFileExtensions do:[:ext |
-                ext notEmpty ifTrue:[
-                    fExt := (f pathName , '.' , ext) asFilename.
-                ] ifFalse:[
-                    fExt := f.
-                ].
-                fExt isExecutable ifTrue:[
-                    ^ fExt pathName
-                ].
-            ].
-        ] ifFalse:[
-            f isExecutable ifTrue:[
-                ^ f pathName
-            ].
-        ].
+	rpath := rentry valueNamed: 'PATH'.
+	rpath notNil ifTrue:[
+	    path := path , self pathSeparator , rpath
+	].
+    ].
+    path := '.;', path.
+    hasSuffix := cmdFile suffix notEmpty.
+
+    (path asCollectionOfSubstringsSeparatedBy:self pathSeparator) do:[:eachDirectory |
+	|file|
+
+	eachDirectory isEmpty ifTrue:[
+	    file := cmdFile
+	] ifFalse:[
+	    file := eachDirectory asFilename construct:aCommand.
+	].
+	hasSuffix ifTrue:[
+	    file isExecutableProgram ifTrue:[
+		^ file pathName.
+	    ].
+	] ifFalse:[
+	    self executableFileExtensions do:[:ext |
+		|fExt|
+
+		fExt := file withSuffix:ext.
+		fExt isExecutableProgram ifTrue:[
+		    ^ fExt pathName.
+		].
+	    ].
+	].
     ].
     ^ nil
 
-    "windows:
-
+    "
      OperatingSystem pathOfCommand:'bcc32'
      OperatingSystem pathOfCommand:'diff'
      OperatingSystem pathOfCommand:'cvs'
      OperatingSystem pathOfCommand:'cvs.exe'
      OperatingSystem pathOfCommand:'stx.exe'
      OperatingSystem pathOfCommand:'stx'
+     OperatingSystem pathOfCommand:'blaFaselQuall'
     "
 
     "Modified: / 20-01-2012 / 13:32:55 / cg"
@@ -3905,16 +3852,16 @@
 
 !
 
-primExec:commandPath commandLine:commandLine fileDescriptors:fdArray fork:doFork newPgrp:newPgrp 
-        inPath:dirName createFlags:flagsOrNil inheritHandles:inheritHandles
-        showWindow:showWindowBooleanOrNil
+primExec:commandPath commandLine:commandLine fileDescriptors:fdArray fork:doFork newPgrp:newPgrp
+	inPath:dirName createFlags:flagsOrNil inheritHandles:inheritHandles
+	showWindow:showWindowBooleanOrNil
     "Internal lowLevel entry for combined fork & exec for WIN32
 
      showWindowBooleanOrNil may be:
-        true  - a window is shown on start of the command
-        false - the command window is hidden
-        nil   - the nCmdShown parameter of the commans's winmain function determins, 
-                if a window is shown."
+	true  - a window is shown on start of the command
+	false - the command window is hidden
+	nil   - the nCmdShown parameter of the commans's winmain function determins,
+		if a window is shown."
 
     |handle commandPathUni16 commandLineUni16 dirNameUni16|
 
@@ -3925,13 +3872,13 @@
     dirNameUni16 := dirName.
 
     commandPathUni16 notNil ifTrue:[
-        commandPathUni16 := commandPathUni16 asUnicode16String.
+	commandPathUni16 := commandPathUni16 asUnicode16String.
     ].
     commandLineUni16 notNil ifTrue:[
-        commandLineUni16 := commandLineUni16 asUnicode16String.
+	commandLineUni16 := commandLineUni16 asUnicode16String.
     ].
     dirNameUni16 notNil ifTrue:[
-        dirNameUni16 := dirNameUni16 asUnicode16String.
+	dirNameUni16 := dirNameUni16 asUnicode16String.
     ].
 
 
@@ -3969,280 +3916,280 @@
     SECURITY_DESCRIPTOR securityDescriptor;
 
     if ((__isUnicode16String(commandPathUni16) || (commandPathUni16 == nil)) && __isUnicode16String(commandLineUni16)) {
-        HANDLE stdinHandle = NULL;
-        HANDLE stdoutHandle = NULL;
-        HANDLE stderrHandle = NULL;
-        int mustClose_stdinHandle = 0;
-        int mustClose_stdoutHandle = 0;
-        int mustClose_stderrHandle = 0;
-
-        /*
-         * terminate the multi byte strings
-         */
-        // #commandPathUni16
-        if (commandPathUni16 != nil) {
-            l = __unicode16StringSize(commandPathUni16);
-            if (l >= 4096) { // >= need 1 space for terminator
-                #ifdef PROCESSDEBUGWIN32
-                console_fprintf(stderr, "argument #commandPathUni16 is to long\n");
-                #endif
-                RETURN(nil);
-            }
-            for (i = 0; i < l; i++) {
-                cmdPathW[i] = __unicode16StringVal(commandPathUni16)[i];
-            }
-            cmdPathW[i] = 0; // set terminator
-            cmdPathWP = &cmdPathW[0];
-        }
-
-        // commandLineUni16
-        l = __unicode16StringSize(commandLineUni16);
-        if (l >= 4096) { // >= need 1 space for terminator
-            #ifdef PROCESSDEBUGWIN32
-            console_fprintf(stderr, "argument #commandLineUni16 is to long\n");
-            #endif
-            RETURN(nil);
-        }
-        for (i = 0; i < l; i++) {
-            cmdLineW[i] = __unicode16StringVal(commandLineUni16)[i];
-        }
-        cmdLineW[i] = 0; // set terminator
-        cmdLineWP = &cmdLineW[0];
-
-        // #dirNameUni16
-        if (__isUnicode16String(dirNameUni16)) {
-            l = __unicode16StringSize(dirNameUni16);
-            if (l >= 4096) { // >= need 1 space for terminator
-                #ifdef PROCESSDEBUGWIN32
-                console_fprintf(stderr, "argument #dirNameUni16 is to long\n");
-                #endif
-                RETURN(nil);
-            }
-            for (i = 0; i < l; i++) {
-                dirNameW[i] = __unicode16StringVal(dirNameUni16)[i];
-            }
-            dirNameW[i] = 0; // set terminator
-            dirNameWP = &dirNameW[0];
-        }
-
-        /*
-         * create descriptors as req'd
-         */
-        memset(&securityAttributes, 0, sizeof(securityAttributes));
-        securityAttributes.nLength = sizeof(securityAttributes);
-        securityAttributes.bInheritHandle = (inheritHandles == true) ? TRUE : FALSE;
-
-        InitializeSecurityDescriptor(&securityDescriptor, SECURITY_DESCRIPTOR_REVISION);
-        SetSecurityDescriptorDacl(&securityDescriptor, -1, 0, 0);
-
-        securityAttributes.lpSecurityDescriptor = &securityDescriptor;
-        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;
-        lpsiStartInfo.dwFlags           = STARTF_USESTDHANDLES /*| STARTF_USEPOSITION*/;
-        if (showWindowBooleanOrNil != nil) {
-            lpsiStartInfo.dwFlags |= STARTF_USESHOWWINDOW;
-            lpsiStartInfo.wShowWindow = showWindowBooleanOrNil == true ? SW_SHOWNORMAL : SW_HIDE;
-        }
-        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 {
-            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) {
-            stdinHandle  = (HANDLE) _get_osfhandle (0);
-            stdoutHandle = (HANDLE) _get_osfhandle (1);
-            stderrHandle  = (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])) {
-                    stdinHandle = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[0]);
-                } else {
-                    stdinHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[0]));
-                }
-            }
-            if (__ArrayInstPtr(fdArray)->a_element[1] != nil) {
-                if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[1])) {
-                    stdoutHandle = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[1]);
-                } else {
-                    stdoutHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[1]));
-                }
-            }
-            if (__ArrayInstPtr(fdArray)->a_element[2] != nil) {
-                if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[2])) {
-                    stderrHandle  = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[2]);
-                } else {
-                    stderrHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[2]));
-                }
-            }
-        } else {
-            console_fprintf(stderr, "Win32OS [warning]: bad fd arg in createProcess\n");
-        }
+	HANDLE stdinHandle = NULL;
+	HANDLE stdoutHandle = NULL;
+	HANDLE stderrHandle = NULL;
+	int mustClose_stdinHandle = 0;
+	int mustClose_stdoutHandle = 0;
+	int mustClose_stderrHandle = 0;
+
+	/*
+	 * terminate the multi byte strings
+	 */
+	// #commandPathUni16
+	if (commandPathUni16 != nil) {
+	    l = __unicode16StringSize(commandPathUni16);
+	    if (l >= 4096) { // >= need 1 space for terminator
+		#ifdef PROCESSDEBUGWIN32
+		console_fprintf(stderr, "argument #commandPathUni16 is to long\n");
+		#endif
+		RETURN(nil);
+	    }
+	    for (i = 0; i < l; i++) {
+		cmdPathW[i] = __unicode16StringVal(commandPathUni16)[i];
+	    }
+	    cmdPathW[i] = 0; // set terminator
+	    cmdPathWP = &cmdPathW[0];
+	}
+
+	// commandLineUni16
+	l = __unicode16StringSize(commandLineUni16);
+	if (l >= 4096) { // >= need 1 space for terminator
+	    #ifdef PROCESSDEBUGWIN32
+	    console_fprintf(stderr, "argument #commandLineUni16 is to long\n");
+	    #endif
+	    RETURN(nil);
+	}
+	for (i = 0; i < l; i++) {
+	    cmdLineW[i] = __unicode16StringVal(commandLineUni16)[i];
+	}
+	cmdLineW[i] = 0; // set terminator
+	cmdLineWP = &cmdLineW[0];
+
+	// #dirNameUni16
+	if (__isUnicode16String(dirNameUni16)) {
+	    l = __unicode16StringSize(dirNameUni16);
+	    if (l >= 4096) { // >= need 1 space for terminator
+		#ifdef PROCESSDEBUGWIN32
+		console_fprintf(stderr, "argument #dirNameUni16 is to long\n");
+		#endif
+		RETURN(nil);
+	    }
+	    for (i = 0; i < l; i++) {
+		dirNameW[i] = __unicode16StringVal(dirNameUni16)[i];
+	    }
+	    dirNameW[i] = 0; // set terminator
+	    dirNameWP = &dirNameW[0];
+	}
+
+	/*
+	 * create descriptors as req'd
+	 */
+	memset(&securityAttributes, 0, sizeof(securityAttributes));
+	securityAttributes.nLength = sizeof(securityAttributes);
+	securityAttributes.bInheritHandle = (inheritHandles == true) ? TRUE : FALSE;
+
+	InitializeSecurityDescriptor(&securityDescriptor, SECURITY_DESCRIPTOR_REVISION);
+	SetSecurityDescriptorDacl(&securityDescriptor, -1, 0, 0);
+
+	securityAttributes.lpSecurityDescriptor = &securityDescriptor;
+	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;
+	lpsiStartInfo.dwFlags           = STARTF_USESTDHANDLES /*| STARTF_USEPOSITION*/;
+	if (showWindowBooleanOrNil != nil) {
+	    lpsiStartInfo.dwFlags |= STARTF_USESHOWWINDOW;
+	    lpsiStartInfo.wShowWindow = showWindowBooleanOrNil == true ? SW_SHOWNORMAL : SW_HIDE;
+	}
+	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 {
+	    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) {
+	    stdinHandle  = (HANDLE) _get_osfhandle (0);
+	    stdoutHandle = (HANDLE) _get_osfhandle (1);
+	    stderrHandle  = (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])) {
+		    stdinHandle = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[0]);
+		} else {
+		    stdinHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[0]));
+		}
+	    }
+	    if (__ArrayInstPtr(fdArray)->a_element[1] != nil) {
+		if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[1])) {
+		    stdoutHandle = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[1]);
+		} else {
+		    stdoutHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[1]));
+		}
+	    }
+	    if (__ArrayInstPtr(fdArray)->a_element[2] != nil) {
+		if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[2])) {
+		    stderrHandle  = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[2]);
+		} else {
+		    stderrHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[2]));
+		}
+	    }
+	} else {
+	    console_fprintf(stderr, "Win32OS [warning]: bad fd arg in createProcess\n");
+	}
 
 #if defined(PROCESSDEBUGWIN32)
-        console_fprintf(stderr, "stdin %x\n", stdinHandle);
-        console_fprintf(stderr, "stdout %x\n", stdoutHandle);
-        console_fprintf(stderr, "stderr %x\n", stderrHandle);
-#endif
-
-        {
-            HANDLE childHandle;
-            int sameHandle = (stdoutHandle == stderrHandle);
-
-            // these MUST be inheritable!
-            if (stdinHandle) {
+	console_fprintf(stderr, "stdin %x\n", stdinHandle);
+	console_fprintf(stderr, "stdout %x\n", stdoutHandle);
+	console_fprintf(stderr, "stderr %x\n", stderrHandle);
+#endif
+
+	{
+	    HANDLE childHandle;
+	    int sameHandle = (stdoutHandle == stderrHandle);
+
+	    // these MUST be inheritable!
+	    if (stdinHandle) {
 #if 0
-                if (SetHandleInformation(stdinHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
-                    // good
-                } else {
-                    console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
-                }
-#else
-                if (DuplicateHandle(GetCurrentProcess(), stdinHandle, GetCurrentProcess(),
-                                      &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
-                    stdinHandle = childHandle;
-                    mustClose_stdinHandle = 1;
-                } else {
-                    console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
-                }
-#endif
-            }
-            if (stdoutHandle) {
+		if (SetHandleInformation(stdinHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
+		    // good
+		} else {
+		    console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
+		}
+#else
+		if (DuplicateHandle(GetCurrentProcess(), stdinHandle, GetCurrentProcess(),
+				      &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
+		    stdinHandle = childHandle;
+		    mustClose_stdinHandle = 1;
+		} else {
+		    console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
+		}
+#endif
+	    }
+	    if (stdoutHandle) {
 #if 0
-                if (SetHandleInformation(stdoutHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
-                    // good
-                } else {
-                    console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
-                }
-#else
-                if (DuplicateHandle(GetCurrentProcess(), stdoutHandle, GetCurrentProcess(),
-                                      &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
-                    stdoutHandle = childHandle;
-                    mustClose_stdoutHandle = 1;
-                } else {
-                    console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
-                }
-#endif
-            }
-            if (stderrHandle) {
-                if (sameHandle) {
-                    stderrHandle = stdoutHandle;
-                } else {
+		if (SetHandleInformation(stdoutHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
+		    // good
+		} else {
+		    console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
+		}
+#else
+		if (DuplicateHandle(GetCurrentProcess(), stdoutHandle, GetCurrentProcess(),
+				      &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
+		    stdoutHandle = childHandle;
+		    mustClose_stdoutHandle = 1;
+		} else {
+		    console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
+		}
+#endif
+	    }
+	    if (stderrHandle) {
+		if (sameHandle) {
+		    stderrHandle = stdoutHandle;
+		} else {
 #if 0
-                    if (SetHandleInformation(stderrHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
-                        // good
-                    } else {
-                        console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
-                    }
-#else
-                    if (DuplicateHandle(GetCurrentProcess(), stderrHandle, GetCurrentProcess(),
-                                          &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
-                        stderrHandle = childHandle;
-                        mustClose_stderrHandle = 1;
-                    } else {
-                        console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
-                    }
-#endif
-                }
-            }
-        }
-        lpsiStartInfo.hStdInput  = stdinHandle;
-        lpsiStartInfo.hStdOutput = stdoutHandle;
-        lpsiStartInfo.hStdError  = stderrHandle;
-
-        if (doFork == true) {
+		    if (SetHandleInformation(stderrHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
+			// good
+		    } else {
+			console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
+		    }
+#else
+		    if (DuplicateHandle(GetCurrentProcess(), stderrHandle, GetCurrentProcess(),
+					  &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
+			stderrHandle = childHandle;
+			mustClose_stderrHandle = 1;
+		    } else {
+			console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
+		    }
+#endif
+		}
+	    }
+	}
+	lpsiStartInfo.hStdInput  = stdinHandle;
+	lpsiStartInfo.hStdOutput = stdoutHandle;
+	lpsiStartInfo.hStdError  = stderrHandle;
+
+	if (doFork == true) {
 #ifdef PROCESSDEBUGWIN32
-            console_fprintf(stderr, "create process cmdPath:<%s> cmdLine:<%s> in <%s>\n", cmdPath, cmdLine, dir);
-#endif
-            if (CreateProcessW( cmdPathWP,
-                                cmdLineWP,
-                                &securityAttributes, NULL /* &securityAttributes */,
-                                securityAttributes.bInheritHandle,      /* inherit handles */
-                                fdwCreate | CREATE_SUSPENDED,           /* resume after setting affinity */
-                                NULL,                                   /* env */
-                                dirNameWP,
-                                &lpsiStartInfo,
-                                &lppiProcInfo ))
-            {
-                DWORD_PTR processAffinityMask, systemAffinityMask;
-
-                /*
-                 * Process was created suspended, now set the affinity mask
-                 * to any processor, and resume the processes main thread.
-                 * (librun/process.s limited the affinity to a single processor).
-                 */
-                GetProcessAffinityMask(lppiProcInfo.hProcess, &processAffinityMask, &systemAffinityMask);
-                SetProcessAffinityMask(lppiProcInfo.hProcess, systemAffinityMask);
-                if ((fdwCreate & CREATE_SUSPENDED) == 0) {
-                    ResumeThread(lppiProcInfo.hThread);
-                }
-                CloseHandle(lppiProcInfo.hThread);
+	    console_fprintf(stderr, "create process cmdPath:<%s> cmdLine:<%s> in <%s>\n", cmdPath, cmdLine, dir);
+#endif
+	    if (CreateProcessW( cmdPathWP,
+				cmdLineWP,
+				&securityAttributes, NULL /* &securityAttributes */,
+				securityAttributes.bInheritHandle,      /* inherit handles */
+				fdwCreate | CREATE_SUSPENDED,           /* resume after setting affinity */
+				NULL,                                   /* env */
+				dirNameWP,
+				&lpsiStartInfo,
+				&lppiProcInfo ))
+	    {
+		DWORD_PTR processAffinityMask, systemAffinityMask;
+
+		/*
+		 * Process was created suspended, now set the affinity mask
+		 * to any processor, and resume the processes main thread.
+		 * (librun/process.s limited the affinity to a single processor).
+		 */
+		GetProcessAffinityMask(lppiProcInfo.hProcess, &processAffinityMask, &systemAffinityMask);
+		SetProcessAffinityMask(lppiProcInfo.hProcess, systemAffinityMask);
+		if ((fdwCreate & CREATE_SUSPENDED) == 0) {
+		    ResumeThread(lppiProcInfo.hThread);
+		}
+		CloseHandle(lppiProcInfo.hThread);
 
 #if 0
-                // only works with real console handles
-                {
-                    // change the child's stdIn (console) mode
-                    DWORD mode = 0;
-
-                    if (! GetConsoleMode(stdinHandle, &mode)) {
-                        console_fprintf(stderr, "Win32OS [warning]: GetConsoleMode failed in createProcess\n");
-                    }
-                    if (! SetConsoleMode(stdinHandle, mode & (~ENABLE_ECHO_INPUT))){
-                        console_fprintf(stderr, "Win32OS [warning]: SetConsoleMode failed in createProcess\n");
-                    }
-                }
-#endif
-                if (mustClose_stdinHandle) {
-                    CloseHandle(stdinHandle);
-                }
-                if (mustClose_stdoutHandle) {
-                    CloseHandle(stdoutHandle);
-                }
-                if (mustClose_stderrHandle) {
-                    CloseHandle(stderrHandle);
-                }
+		// only works with real console handles
+		{
+		    // change the child's stdIn (console) mode
+		    DWORD mode = 0;
+
+		    if (! GetConsoleMode(stdinHandle, &mode)) {
+			console_fprintf(stderr, "Win32OS [warning]: GetConsoleMode failed in createProcess\n");
+		    }
+		    if (! SetConsoleMode(stdinHandle, mode & (~ENABLE_ECHO_INPUT))){
+			console_fprintf(stderr, "Win32OS [warning]: SetConsoleMode failed in createProcess\n");
+		    }
+		}
+#endif
+		if (mustClose_stdinHandle) {
+		    CloseHandle(stdinHandle);
+		}
+		if (mustClose_stdoutHandle) {
+		    CloseHandle(stdoutHandle);
+		}
+		if (mustClose_stderrHandle) {
+		    CloseHandle(stderrHandle);
+		}
 #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 */
+	}
     }
 %}.
     "
@@ -4259,7 +4206,7 @@
      If its a directory, an explorer window is opened (see example below).
      Can be used to open a browser or viewer on html-files, pdf-files etc.
      lpDirectory: the pathname string of the directory used for the command,
-                  or nil for the current directory."
+		  or nil for the current directory."
 
     |errorNumber handle|
 
@@ -4270,206 +4217,98 @@
     shExecInfo.cbSize = sizeof(shExecInfo);
 
     if (__isSmallInteger(nShowCmd)) {
-        shExecInfo.nShow = __intVal(nShowCmd);
+	shExecInfo.nShow = __intVal(nShowCmd);
     } else {
-        if (nShowCmd == @symbol(SW_SHOW)) {
-            shExecInfo.nShow = SW_SHOW;
-        } else if (nShowCmd == @symbol(SW_SHOWNORMAL)) {
-            shExecInfo.nShow = SW_SHOWNORMAL;
-        } else if (nShowCmd == @symbol(SW_SHOWDEFAULT)) {
-            shExecInfo.nShow = SW_SHOWDEFAULT;
-        } else if (nShowCmd == @symbol(SW_SHOWMAXIMIZED)) {
-            shExecInfo.nShow = SW_SHOWMAXIMIZED;
-        } else if (nShowCmd == @symbol(SW_SHOWMINIMIZED)) {
-            shExecInfo.nShow = SW_SHOWMINIMIZED;
-        } else if (nShowCmd == @symbol(SW_SHOWMINNOACTIVE)) {
-            shExecInfo.nShow = SW_SHOWMINNOACTIVE;
-        } else if (nShowCmd == @symbol(SW_SHOWNA)) {
-            shExecInfo.nShow = SW_SHOWNA;
-        } else if (nShowCmd == @symbol(SW_SHOWNOACTIVATE)) {
-            shExecInfo.nShow = SW_SHOWNOACTIVATE;
-        } else if (nShowCmd == @symbol(SW_MAXIMIZE)) {
-            shExecInfo.nShow = SW_MAXIMIZE;
-        } else if (nShowCmd == @symbol(SW_RESTORE)) {
-            shExecInfo.nShow = SW_RESTORE;
-        } else {
-            goto badArgument;
-        }
+	if (nShowCmd == @symbol(SW_SHOW)) {
+	    shExecInfo.nShow = SW_SHOW;
+	} else if (nShowCmd == @symbol(SW_SHOWNORMAL)) {
+	    shExecInfo.nShow = SW_SHOWNORMAL;
+	} else if (nShowCmd == @symbol(SW_SHOWDEFAULT)) {
+	    shExecInfo.nShow = SW_SHOWDEFAULT;
+	} else if (nShowCmd == @symbol(SW_SHOWMAXIMIZED)) {
+	    shExecInfo.nShow = SW_SHOWMAXIMIZED;
+	} else if (nShowCmd == @symbol(SW_SHOWMINIMIZED)) {
+	    shExecInfo.nShow = SW_SHOWMINIMIZED;
+	} else if (nShowCmd == @symbol(SW_SHOWMINNOACTIVE)) {
+	    shExecInfo.nShow = SW_SHOWMINNOACTIVE;
+	} else if (nShowCmd == @symbol(SW_SHOWNA)) {
+	    shExecInfo.nShow = SW_SHOWNA;
+	} else if (nShowCmd == @symbol(SW_SHOWNOACTIVATE)) {
+	    shExecInfo.nShow = SW_SHOWNOACTIVATE;
+	} else if (nShowCmd == @symbol(SW_MAXIMIZE)) {
+	    shExecInfo.nShow = SW_MAXIMIZE;
+	} else if (nShowCmd == @symbol(SW_RESTORE)) {
+	    shExecInfo.nShow = SW_RESTORE;
+	} else {
+	    goto badArgument;
+	}
     }
     if (((lpOperationArg == nil) || __isStringLike(lpOperationArg))
      && ((lpFileArg == nil) || __isStringLike(lpFileArg))
      && ((lpParametersArg == nil) || __isStringLike(lpParametersArg))
      && ((lpDirectoryArg == nil) || __isStringLike(lpDirectoryArg))
     ) {
-        // hProcess member receives the process handle
-        shExecInfo.fMask = SEE_MASK_NOCLOSEPROCESS;
-
-        shExecInfo.hwnd = 0;
-        shExecInfo.lpVerb        = (lpOperationArg != nil) ? __stringVal(lpOperationArg) : NULL;
-        shExecInfo.lpFile        = (lpFileArg != nil) ? __stringVal(lpFileArg) : NULL;
-        shExecInfo.lpParameters  = (lpParametersArg != nil) ? __stringVal(lpParametersArg) : NULL;
-        shExecInfo.lpDirectory   = (lpDirectoryArg != nil) ? __stringVal(lpDirectoryArg) : NULL;
-        if (hwndArg != nil) {
-            if (__isExternalAddressLike(hwndArg)) {
-                shExecInfo.hwnd = _HANDLEVal(hwndArg);
-            } else
-                goto badArgument;
-        }
-        if (ShellExecuteEx(&shExecInfo)) {
-            if (shExecInfo.hProcess) {
-                DWORD_PTR processAffinityMask, systemAffinityMask;
-                /*
-                 * Set the affinity mask
-                 * to any processor, and resume the processes main thread.
-                 * (librun/process.s limited the affinity to a single processor).
-                 */
-                GetProcessAffinityMask(shExecInfo.hProcess, &processAffinityMask, &systemAffinityMask);
-                SetProcessAffinityMask(shExecInfo.hProcess, systemAffinityMask);
-
-                __externalAddressVal(handle) = shExecInfo.hProcess;
-                RETURN (handle);
-            } else {
-                RETURN (nil); /* OK */
-            }
-        } else {
-            /* error */
-            errorNumber = __mkSmallInteger(__WIN32_ERR(GetLastError()));
-        }
+	// hProcess member receives the process handle
+	shExecInfo.fMask = SEE_MASK_NOCLOSEPROCESS;
+
+	shExecInfo.hwnd = 0;
+	shExecInfo.lpVerb        = (lpOperationArg != nil) ? __stringVal(lpOperationArg) : NULL;
+	shExecInfo.lpFile        = (lpFileArg != nil) ? __stringVal(lpFileArg) : NULL;
+	shExecInfo.lpParameters  = (lpParametersArg != nil) ? __stringVal(lpParametersArg) : NULL;
+	shExecInfo.lpDirectory   = (lpDirectoryArg != nil) ? __stringVal(lpDirectoryArg) : NULL;
+	if (hwndArg != nil) {
+	    if (__isExternalAddressLike(hwndArg)) {
+		shExecInfo.hwnd = _HANDLEVal(hwndArg);
+	    } else
+		goto badArgument;
+	}
+	if (ShellExecuteEx(&shExecInfo)) {
+	    if (shExecInfo.hProcess) {
+		DWORD_PTR processAffinityMask, systemAffinityMask;
+		/*
+		 * Set the affinity mask
+		 * to any processor, and resume the processes main thread.
+		 * (librun/process.s limited the affinity to a single processor).
+		 */
+		GetProcessAffinityMask(shExecInfo.hProcess, &processAffinityMask, &systemAffinityMask);
+		SetProcessAffinityMask(shExecInfo.hProcess, systemAffinityMask);
+
+		__externalAddressVal(handle) = shExecInfo.hProcess;
+		RETURN (handle);
+	    } else {
+		RETURN (nil); /* OK */
+	    }
+	} else {
+	    /* error */
+	    errorNumber = __mkSmallInteger(__WIN32_ERR(GetLastError()));
+	}
     }
 badArgument: ;
 %}.
     errorNumber isNil ifTrue:[
-        self primitiveFailed:'invalid argument(s)'.
+	self primitiveFailed:'invalid argument(s)'.
     ] ifFalse:[
-        (OperatingSystem errorHolderForNumber:errorNumber)
-            parameter:lpFileArg;
-            reportError
+	(OperatingSystem errorHolderForNumber:errorNumber)
+	    parameter:lpFileArg;
+	    reportError
     ].
 
     "
      self
-        shellExecute:nil
-        lpOperation:'open'
-        lpFile:(Filename currentDirectory pathName)
-        lpParameters:nil
-        lpDirectory:nil
-        nShowCmd:#SW_SHOWNORMAL
+	shellExecute:nil
+	lpOperation:'open'
+	lpFile:(Filename currentDirectory pathName)
+	lpParameters:nil
+	lpDirectory:nil
+	nShowCmd:#SW_SHOWNORMAL
     self
-        shellExecute:nil
-        lpOperation:'explore'
-        lpFile:(Filename currentDirectory pathName)
-        lpParameters:nil
-        lpDirectory:nil
-        nShowCmd:#SW_SHOWNORMAL
-    "
-!
-
-startProcess:aCommandString inputFrom:anExternalInStream outputTo:anExternalOutStream
-    errorTo:anExternalErrStream auxFrom:anAuxiliaryStream
-    environment:anEvironmentDictionary inDirectory:dir
-
-    "start executing the OS command as specified by the argument, aCommandString
-     as a separate process; do not wait for the command to finish.
-     If aCommandString is a String, the commandString is passed to a shell for execution
-     - see the description of 'sh -c' in your UNIX manual ('cmd.com' in your MSDOS manual).
-     If aCommandString is an Array, the first element is the command to be executed,
-     and the other elements are the arguments to the command. No shell is invoked in this case.
-     The command gets stdIn, stdOut and stdErr assigned from the arguments;
-     each may be nil.
-
-     Return the Win32ProcessHandle if successful, nil otherwise.
-
-     Use #monitorPid:action: for synchronization and exec status return,
-     or #killProcess: to stop it."
-
-    ^ self
-        startProcess:aCommandString inputFrom:anExternalInStream outputTo:anExternalOutStream
-        errorTo:anExternalErrStream auxFrom:anAuxiliaryStream
-        environment:anEvironmentDictionary inDirectory:dir
-        showWindow:nil
-
-    "blocking at current prio (i.e. only higher prio threads execute):
-
-     OperatingSystem executeCommand:'dir > out'.
-     OperatingSystem executeCommand:'tree /A' outputTo:Transcript.
-     OperatingSystem executeCommand:#('c:\windows\system32\tree.com' '/A' '/F') outputTo:Transcript.
-     OperatingSystem executeCommand:#('c:\windows\system32\where.exe' '/T' '*.dll') outputTo:Transcript.
-    "
-
-    "non-blocking (lower prio threads continue):
-
-     |in out err pid sema|
-
-     in := 'out' asFilename readStream.
-     out := 'out2' asFilename writeStream.
-     err := 'err' asFilename writeStream.
-
-     sema := Semaphore new.
-     pid := OperatingSystem startProcess:'sleep 10; grep drw' inputFrom:in outputTo:out errorTo:err.
-
-     The following will no longer work. monitorPid has disappeared
-
-     pid notNil ifTrue:[
-         Processor monitorPid:pid action:[:OSstatus | sema signal ].
-     ].
-     in close.
-     out close.
-     err close.
-     sema wait.
-     Transcript showCR:'finished'
-    "
-
-    "
-     |pid sema|
-
-     sema := Semaphore new.
-
-     Processor
-            monitor:[
-                pid := OperatingSystem startProcess:'dir > out 2>err'
-            ]
-            action:[:osStatus | sema signal ].
-
-     sema wait.
-     Transcript showCR:'finished'
-    "
-
-"<<END
-     |pid sema|
-
-     sema := Semaphore new.
-
-     Processor
-            monitor:[
-                pid := OperatingSystem startProcess:'(echo 1 & stx --eval "Delay waitForSeconds:100" & dir) >out' withCRs
-            ]
-            action:[:osStatus | sema signal ].
-
-     Delay waitForSeconds:5.
-     OperatingSystem terminateProcessGroup:pid.
-     Transcript showCR:'terminated'
-END"
-
-"<<END
-     |pid sema|
-
-     sema := Semaphore new.
-
-     Processor
-            monitor:[
-                pid := OperatingSystem startProcess:{ 'C:\Users\cg\work\stx\projects\smalltalk\stx.com' . '--eval' . '"Delay waitForSeconds:100"' }
-            ]
-            action:[:osStatus | sema signal ].
-
-     Delay waitForSeconds:5.
-     OperatingSystem terminateProcess:pid.
-     Transcript showCR:'terminated'
-END"
-
-    "Modified: / 21-03-1997 / 10:04:35 / dq"
-    "Modified: / 15-07-1997 / 16:03:51 / stefan"
-    "Created: / 12-11-1998 / 14:39:20 / cg"
-    "Modified: / 30-06-2016 / 17:43:46 / cg"
+	shellExecute:nil
+	lpOperation:'explore'
+	lpFile:(Filename currentDirectory pathName)
+	lpParameters:nil
+	lpDirectory:nil
+	nShowCmd:#SW_SHOWNORMAL
+    "
 !
 
 startProcess:aCommandString inputFrom:anExternalInStream outputTo:anExternalOutStream
@@ -4497,32 +4336,32 @@
     shellAndArgs := self commandAndArgsForOSCommand:aCommandString.
 
     (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
     ].
 
     rslt := self
-        exec:(shellAndArgs at:1)
-        withArguments:(shellAndArgs at:2)
-        environment:anEvironmentDictionary
-        fileDescriptors:(Array with:in fileHandle
-                               with:out fileHandle
-                               with:err fileHandle
-                               with:(anAuxiliaryStream notNil ifTrue:[anAuxiliaryStream fileHandle] ifFalse:[nil]))
-        fork:true
-        newPgrp:true
-        inDirectory:dir
-        showWindow:showWindowBooleanOrNil.
+	exec:(shellAndArgs at:1)
+	withArguments:(shellAndArgs at:2)
+	environment:anEvironmentDictionary
+	fileDescriptors:(Array with:in fileHandle
+			       with:out fileHandle
+			       with:err fileHandle
+			       with:(anAuxiliaryStream notNil ifTrue:[anAuxiliaryStream fileHandle] ifFalse:[nil]))
+	fork:true
+	newPgrp:true
+	inDirectory:dir
+	showWindow:(showWindowBooleanOrNil ? (shellAndArgs at:3)).
 
     nullStream notNil ifTrue:[
-        nullStream close.
+	nullStream close.
     ].
     ^ rslt
 
@@ -4548,7 +4387,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.
@@ -4563,10 +4402,10 @@
      sema := Semaphore new.
 
      Processor
-            monitor:[
-                pid := OperatingSystem startProcess:'dir > out 2>err'
-            ]
-            action:[:osStatus | sema signal ].
+	    monitor:[
+		pid := OperatingSystem startProcess:'dir > out 2>err'
+	    ]
+	    action:[:osStatus | sema signal ].
 
      sema wait.
      Transcript showCR:'finished'
@@ -4578,10 +4417,10 @@
      sema := Semaphore new.
 
      Processor
-            monitor:[
-                pid := OperatingSystem startProcess:'(echo 1 & stx --eval "Delay waitForSeconds:100" & dir) >out' withCRs
-            ]
-            action:[:osStatus | sema signal ].
+	    monitor:[
+		pid := OperatingSystem startProcess:'(echo 1 & stx --eval "Delay waitForSeconds:100" & dir) >out' withCRs
+	    ]
+	    action:[:osStatus | sema signal ].
 
      Delay waitForSeconds:5.
      OperatingSystem terminateProcessGroup:pid.
@@ -4594,10 +4433,10 @@
      sema := Semaphore new.
 
      Processor
-            monitor:[
-                pid := OperatingSystem startProcess:{ 'C:\Users\cg\work\stx\projects\smalltalk\stx.com' . '--eval' . '"Delay waitForSeconds:100"' }
-            ]
-            action:[:osStatus | sema signal ].
+	    monitor:[
+		pid := OperatingSystem startProcess:{ 'C:\Users\cg\work\stx\projects\smalltalk\stx.com' . '--eval' . '"Delay waitForSeconds:100"' }
+	    ]
+	    action:[:osStatus | sema signal ].
 
      Delay waitForSeconds:5.
      OperatingSystem terminateProcess:pid.
@@ -4617,12 +4456,12 @@
 
 %{
     if (__isSmallInteger(anIntegerOrHandle)) {
-        close(__intVal(anIntegerOrHandle));
-        RETURN(self);
+	close(__intVal(anIntegerOrHandle));
+	RETURN(self);
     }
     if (__isExternalAddressLike(anIntegerOrHandle)) {
        if (!CloseHandle( _HANDLEVal(anIntegerOrHandle))) {
-           console_fprintf( stderr, "Win32OS [warning]: Could not close handle : %x\n", _HANDLEVal(anIntegerOrHandle));
+	   console_fprintf( stderr, "Win32OS [warning]: Could not close handle : %x\n", _HANDLEVal(anIntegerOrHandle));
        }
        RETURN(self);
     }
@@ -4649,28 +4488,28 @@
     sa.bInheritHandle = FALSE;
 
     if (__isStringLike(aPathName)) {
-        int ret;
-
-        ret = CreateDirectoryA(__stringVal(aPathName), &sa);
-        if (ret != TRUE) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
+	int ret;
+
+	ret = CreateDirectoryA(__stringVal(aPathName), &sa);
+	if (ret != TRUE) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN (false);
+	}
+	RETURN (true);
     }
     if (__isUnicode16String(aPathName)) {
-        int ret;
-        wchar_t _wPathName[MAXPATHLEN+1];
-
-        _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
-        ret = CreateDirectoryW(_wPathName, &sa);
-        if (ret != TRUE) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
+	int ret;
+	wchar_t _wPathName[MAXPATHLEN+1];
+
+	_makeWchar(aPathName, _wPathName, sizeof(_wPathName));
+	ret = CreateDirectoryW(_wPathName, &sa);
+	if (ret != TRUE) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN (false);
+	}
+	RETURN (true);
     }
 %}.
     ^ self primitiveFailed
@@ -4735,32 +4574,32 @@
     char szGotPath[MAXPATHLEN];
 
     if (! __isStringLike(aPathName)) {
-        console_fprintf(stderr, "OperatingSystem [info]: invalid argument\n");
-        goto error;
+	console_fprintf(stderr, "OperatingSystem [info]: invalid argument\n");
+	goto error;
     }
 
     if( ! coInitialized ) {
-        console_fprintf(stderr, "OperatingSystem [info]: com not initialized\n");
-        goto error;
+	console_fprintf(stderr, "OperatingSystem [info]: com not initialized\n");
+	goto error;
     }
 
     if ( ipShellLink == NULL ) {
-        hres = CoCreateInstance(&CLSID_ShellLink, NULL, CLSCTX_INPROC_SERVER,
-                                &IID_IShellLink, (LPVOID *)&ipShellLink);
-        if (! SUCCEEDED(hres)) {
-            console_fprintf(stderr, "OperatingSystem [info]: CoCreateInstance Error - hres = %08x\n", hres);
-            ipShellLink = NULL;
-            goto error;
-        }
-
-        hres = ipShellLink->lpVtbl->QueryInterface( ipShellLink, &IID_IPersistFile, (void **)&ipPersistFile );
-        if (! SUCCEEDED(hres)) {
-            console_fprintf(stderr, "OperatingSystem [info]: QueryInterface Error - hres = %08x\n", hres);
-            ipShellLink->lpVtbl->Release(ipShellLink);
-            ipShellLink   = NULL;
-            ipPersistFile = NULL;
-            goto error;
-        }
+	hres = CoCreateInstance(&CLSID_ShellLink, NULL, CLSCTX_INPROC_SERVER,
+				&IID_IShellLink, (LPVOID *)&ipShellLink);
+	if (! SUCCEEDED(hres)) {
+	    console_fprintf(stderr, "OperatingSystem [info]: CoCreateInstance Error - hres = %08x\n", hres);
+	    ipShellLink = NULL;
+	    goto error;
+	}
+
+	hres = ipShellLink->lpVtbl->QueryInterface( ipShellLink, &IID_IPersistFile, (void **)&ipPersistFile );
+	if (! SUCCEEDED(hres)) {
+	    console_fprintf(stderr, "OperatingSystem [info]: QueryInterface Error - hres = %08x\n", hres);
+	    ipShellLink->lpVtbl->Release(ipShellLink);
+	    ipShellLink   = NULL;
+	    ipPersistFile = NULL;
+	    goto error;
+	}
     }
 
     MultiByteToWideChar(CP_ACP, 0, __stringVal(aPathName), -1, wsz, MAXPATHLEN);
@@ -4768,18 +4607,18 @@
     hres = ipPersistFile->lpVtbl->Load(ipPersistFile, wsz, STGM_READ);
 
     if (SUCCEEDED(hres)) {
-        hres = ipShellLink->lpVtbl->GetPath(ipShellLink, szGotPath, MAXPATHLEN,
-                    (WIN32_FIND_DATA *)&wfd, 0 /* SLGP_SHORTPATH */ );
-        if (SUCCEEDED(hres)) {
-            resolvedPath = __MKSTRING(szGotPath);
-        } else {
+	hres = ipShellLink->lpVtbl->GetPath(ipShellLink, szGotPath, MAXPATHLEN,
+		    (WIN32_FIND_DATA *)&wfd, 0 /* SLGP_SHORTPATH */ );
+	if (SUCCEEDED(hres)) {
+	    resolvedPath = __MKSTRING(szGotPath);
+	} else {
 #ifdef COM_DEBUG
-            console_fprintf(stderr, "OperatingSystem [info]: GetPath failed - hres = %08x\n", hres );
-#endif
-        }
+	    console_fprintf(stderr, "OperatingSystem [info]: GetPath failed - hres = %08x\n", hres );
+#endif
+	}
     } else {
 #ifdef COM_DEBUG
-        console_fprintf(stderr, "OperatingSystem [info]: Load failed - hres = %08x\n", hres );
+	console_fprintf(stderr, "OperatingSystem [info]: Load failed - hres = %08x\n", hres );
 #endif
     }
     /* ipPersistFile->lpVtbl->Release(ipPersistFile);  */
@@ -4805,10 +4644,10 @@
      Return true if successful, false if not."
 
     (oldPath isString not or:[newPath isString not]) ifTrue:[
-        "/
-        "/ bad argument(s) given
-        "/
-        ^ self primitiveFailed
+	"/
+	"/ bad argument(s) given
+	"/
+	^ self primitiveFailed
     ].
 
     ^ self createHardLinkFrom:oldPath to:newPath
@@ -4840,19 +4679,19 @@
     DWORD access, share, create, attr;
 
     if (__isStringLike(pathName)) {
-        name = __stringVal(pathName);
+	name = __stringVal(pathName);
     } else if (__isUnicode16String(pathName)) {
-        _makeWchar(pathName, _wPathName, sizeof(_wPathName));
+	_makeWchar(pathName, _wPathName, sizeof(_wPathName));
     } else {
-        fileHandle = nil;
-        argumentError = @symbol(badPathName);
-        goto badArgument;
+	fileHandle = nil;
+	argumentError = @symbol(badPathName);
+	goto badArgument;
     }
 
     if (! __isArrayLike(attributeSpec)) {
-        fileHandle = nil;
-        argumentError = @symbol(badAttributeSpec);
-        goto badArgument;
+	fileHandle = nil;
+	argumentError = @symbol(badAttributeSpec);
+	goto badArgument;
     }
     ap = __ArrayInstPtr(attributeSpec)->a_element;
     numAttrib = __arraySize(attributeSpec);
@@ -4863,77 +4702,77 @@
     attr = 0;
 
     for (i=0; i<numAttrib;i++) {
-        OBJ attrSym = ap[i];
-
-        if (attrSym == @symbol(FILE_SHARE_READ)) {
-            share |= FILE_SHARE_READ;
-        } else if (attrSym == @symbol(FILE_SHARE_WRITE)) {
-            share |= FILE_SHARE_WRITE;
-
-        } else if (attrSym == @symbol(GENERIC_READ)) {
-            access |= GENERIC_READ;
-        } else if (attrSym == @symbol(GENERIC_WRITE)) {
-            access |= GENERIC_WRITE;
-
-        } else if (attrSym == @symbol(CREATE_NEW)) {
-            create |= CREATE_NEW;
-        } else if (attrSym == @symbol(CREATE_ALWAYS)) {
-            create |= CREATE_ALWAYS;
-        } else if (attrSym == @symbol(OPEN_EXISTING)) {
-            create |= OPEN_EXISTING;
-        } else if (attrSym == @symbol(OPEN_ALWAYS)) {
-            create |= OPEN_ALWAYS;
-        } else if (attrSym == @symbol(TRUNCATE_EXISTING)) {
-            create |= TRUNCATE_EXISTING;
-
-        } else if (attrSym == @symbol(FILE_ATTRIBUTE_HIDDEN)) {
-            attr |= FILE_ATTRIBUTE_HIDDEN;
-        } else if (attrSym == @symbol(FILE_ATTRIBUTE_READONLY)) {
-            attr |= FILE_ATTRIBUTE_READONLY;
-        } else if (attrSym == @symbol(FILE_ATTRIBUTE_READONLY)) {
-            attr |= FILE_ATTRIBUTE_READONLY;
-        } else if (attrSym == @symbol(FILE_FLAG_WRITE_THROUGH)) {
-            attr |= FILE_FLAG_WRITE_THROUGH;
-        } else if (attrSym == @symbol(FILE_FLAG_SEQUENTIAL_SCAN)) {
-            attr |= FILE_FLAG_SEQUENTIAL_SCAN;
-        } else if (attrSym == @symbol(FILE_FLAG_DELETE_ON_CLOSE)) {
-            attr |= FILE_FLAG_DELETE_ON_CLOSE;
-        } else {
-            console_fprintf(stderr, "Win32OS [warning]: unsupported open mode\n");
-        }
+	OBJ attrSym = ap[i];
+
+	if (attrSym == @symbol(FILE_SHARE_READ)) {
+	    share |= FILE_SHARE_READ;
+	} else if (attrSym == @symbol(FILE_SHARE_WRITE)) {
+	    share |= FILE_SHARE_WRITE;
+
+	} else if (attrSym == @symbol(GENERIC_READ)) {
+	    access |= GENERIC_READ;
+	} else if (attrSym == @symbol(GENERIC_WRITE)) {
+	    access |= GENERIC_WRITE;
+
+	} else if (attrSym == @symbol(CREATE_NEW)) {
+	    create |= CREATE_NEW;
+	} else if (attrSym == @symbol(CREATE_ALWAYS)) {
+	    create |= CREATE_ALWAYS;
+	} else if (attrSym == @symbol(OPEN_EXISTING)) {
+	    create |= OPEN_EXISTING;
+	} else if (attrSym == @symbol(OPEN_ALWAYS)) {
+	    create |= OPEN_ALWAYS;
+	} else if (attrSym == @symbol(TRUNCATE_EXISTING)) {
+	    create |= TRUNCATE_EXISTING;
+
+	} else if (attrSym == @symbol(FILE_ATTRIBUTE_HIDDEN)) {
+	    attr |= FILE_ATTRIBUTE_HIDDEN;
+	} else if (attrSym == @symbol(FILE_ATTRIBUTE_READONLY)) {
+	    attr |= FILE_ATTRIBUTE_READONLY;
+	} else if (attrSym == @symbol(FILE_ATTRIBUTE_READONLY)) {
+	    attr |= FILE_ATTRIBUTE_READONLY;
+	} else if (attrSym == @symbol(FILE_FLAG_WRITE_THROUGH)) {
+	    attr |= FILE_FLAG_WRITE_THROUGH;
+	} else if (attrSym == @symbol(FILE_FLAG_SEQUENTIAL_SCAN)) {
+	    attr |= FILE_FLAG_SEQUENTIAL_SCAN;
+	} else if (attrSym == @symbol(FILE_FLAG_DELETE_ON_CLOSE)) {
+	    attr |= FILE_FLAG_DELETE_ON_CLOSE;
+	} else {
+	    console_fprintf(stderr, "Win32OS [warning]: unsupported open mode\n");
+	}
     }
     if (create == 0) {
-        fileHandle = nil;
-        argumentError = @symbol(missingCreateMode);
-        goto badArgument;
+	fileHandle = nil;
+	argumentError = @symbol(missingCreateMode);
+	goto badArgument;
     }
 #ifdef PROCESSDEBUGWIN32
     console_fprintf(stderr, "name:<%s> access:%x share:%x create:%x attr:%x\n",
-                name, access, share, create, attr);
+		name, access, share, create, attr);
 #endif
     if (__isStringLike(pathName)) {
-        h = CreateFileA(name, access, share, 0 /* sa */, create, attr, 0 /* hTempl */);
+	h = CreateFileA(name, access, share, 0 /* sa */, create, attr, 0 /* hTempl */);
     } else {
-        h = CreateFileW(_wPathName, access, share, 0 /* sa */, create, attr, 0 /* hTempl */);
+	h = CreateFileW(_wPathName, access, share, 0 /* sa */, create, attr, 0 /* hTempl */);
     }
 
     if (h != INVALID_HANDLE_VALUE) {
-        __externalAddressVal(fileHandle) = (void *)h;
+	__externalAddressVal(fileHandle) = (void *)h;
     } else {
-        fileHandle = nil;
-        errorNumber = __mkSmallInteger( __WIN32_ERR(GetLastError()) );
+	fileHandle = nil;
+	errorNumber = __mkSmallInteger( __WIN32_ERR(GetLastError()) );
     }
 
 badArgument: ;
 %}.
     fileHandle notNil ifTrue:[
-        fileHandle registerForFinalization.
-        ^ fileHandle.
+	fileHandle registerForFinalization.
+	^ fileHandle.
     ].
     errorNumber isNil ifTrue:[
-        self error:'invalid argument(s): ', argumentError.
+	self error:'invalid argument(s): ', argumentError.
     ] ifFalse:[
-        (self errorHolderForNumber:errorNumber) reportError
+	(self errorHolderForNumber:errorNumber) reportError
     ].
 !
 
@@ -4979,46 +4818,46 @@
 
     if (__isStringLike(fullPathName)) {
 #ifdef DO_WRAP_CALLS
-        {
-            char _aPathName[MAXPATHLEN];
-
-            strncpy(_aPathName, __stringVal(fullPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-            do {
-                __threadErrno = 0;
-                // do not cast to INT - will loose sign bit then!
-                ret = (int)(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;
+		// do not cast to INT - will loose sign bit then!
+		ret = (int)(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);
     } else if (__isUnicode16String(fullPathName)) {
 #ifdef DO_WRAP_CALLS
-        {
-            wchar_t _wPathName[MAXPATHLEN+1];
-
-            _makeWchar(fullPathName, _wPathName, sizeof(_wPathName));
-            do {
-                __threadErrno = 0;
-                // do not cast to INT - will loose sign bit then!
-                ret = (int)(STX_API_NOINT_CALL1( "RemoveDirectoryW", RemoveDirectoryW, _wPathName));
-            } while ((ret < 0) && (__threadErrno == EINTR));
-        }
-#else
-        ret = RemoveDirectoryW((wchar_t *)__unicode16StringVal(fullPathName));
-        __threadErrno = __WIN32_ERR(GetLastError());
-#endif
-        if (ret != TRUE) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
+	{
+	    wchar_t _wPathName[MAXPATHLEN+1];
+
+	    _makeWchar(fullPathName, _wPathName, sizeof(_wPathName));
+	    do {
+		__threadErrno = 0;
+		// do not cast to INT - will loose sign bit then!
+		ret = (int)(STX_API_NOINT_CALL1( "RemoveDirectoryW", RemoveDirectoryW, _wPathName));
+	    } while ((ret < 0) && (__threadErrno == EINTR));
+	}
+#else
+	ret = RemoveDirectoryW((wchar_t *)__unicode16StringVal(fullPathName));
+	__threadErrno = __WIN32_ERR(GetLastError());
+#endif
+	if (ret != TRUE) {
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN (false);
+	}
+	RETURN (true);
     }
 %}.
     "/
@@ -5042,47 +4881,47 @@
 
     if (__isStringLike(fullPathName)) {
 #ifdef DO_WRAP_CALLS
-        {
-            char _aPathName[MAXPATHLEN];
-
-            strncpy(_aPathName, __stringVal(fullPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-            do {
-                __threadErrno = 0;
-                // do not cast to INT - will loose sign bit then!
-                ret = (int)(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;
+		// do not cast to INT - will loose sign bit then!
+		ret = (int)(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];
-
-            _makeWchar(fullPathName, _wPathName, sizeof(_wPathName));
-            do {
-                __threadErrno = 0;
-                // do not cast to INT - will loose sign bit then!
-                ret = (int)(STX_API_NOINT_CALL1( "DeleteFileW", DeleteFileW, _wPathName));
-            } while ((ret < 0) && (__threadErrno == EINTR));
-        }
-#else
-        ret = DeleteFileW((wchar_t *)__unicode16StringVal(fullPathName));
-        __threadErrno = __WIN32_ERR(GetLastError());
-#endif
-        if (ret != TRUE) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
+	{
+	    wchar_t _wPathName[MAXPATHLEN+1];
+
+	    _makeWchar(fullPathName, _wPathName, sizeof(_wPathName));
+	    do {
+		__threadErrno = 0;
+		// do not cast to INT - will loose sign bit then!
+		ret = (int)(STX_API_NOINT_CALL1( "DeleteFileW", DeleteFileW, _wPathName));
+	    } while ((ret < 0) && (__threadErrno == EINTR));
+	}
+#else
+	ret = DeleteFileW((wchar_t *)__unicode16StringVal(fullPathName));
+	__threadErrno = __WIN32_ERR(GetLastError());
+#endif
+	if (ret != TRUE) {
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	    RETURN (false);
+	}
+	RETURN (true);
     }
 
 %}.
@@ -5102,57 +4941,57 @@
 
     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;
-            // do not cast to INT - will loose sign bit then!
-            ret = STX_API_NOINT_CALL2("MoveFileA", MoveFileA, _oldPath, _newPath);
-        } while ((ret == 0) && (__threadErrno == EINTR));
-#else
-        __BEGIN_INTERRUPTABLE__
-        do {
-            __threadErrno = 0;
-            ret = MoveFileA((char *) __stringVal(oldPath), (char *) __stringVal(newPath));
-        } while ((ret == 0) && (__threadErrno == EINTR));
-        __END_INTERRUPTABLE__
-
-        if (ret == 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
+	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;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = STX_API_NOINT_CALL2("MoveFileA", MoveFileA, _oldPath, _newPath);
+	} while ((ret == 0) && (__threadErrno == EINTR));
+#else
+	__BEGIN_INTERRUPTABLE__
+	do {
+	    __threadErrno = 0;
+	    ret = MoveFileA((char *) __stringVal(oldPath), (char *) __stringVal(newPath));
+	} while ((ret == 0) && (__threadErrno == EINTR));
+	__END_INTERRUPTABLE__
+
+	if (ret == 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
 #endif
     } else {
-        wchar_t _oldPathW[MAXPATHLEN], _newPathW[MAXPATHLEN];
-
-        if (_makeWchar(oldPath, _oldPathW, sizeof(_oldPathW)) < 0
-            || _makeWchar(newPath, _newPathW, sizeof(_newPathW)) < 0) {
-            goto err;
-        }
+	wchar_t _oldPathW[MAXPATHLEN], _newPathW[MAXPATHLEN];
+
+	if (_makeWchar(oldPath, _oldPathW, sizeof(_oldPathW)) < 0
+	    || _makeWchar(newPath, _newPathW, sizeof(_newPathW)) < 0) {
+	    goto err;
+	}
 #ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = STX_API_NOINT_CALL2( "MoveFileW", MoveFileW, _oldPathW, _newPathW);
-        } while ((ret == 0) && (__threadErrno == EINTR));
-#else
-        __BEGIN_INTERRUPTABLE__
-        do {
-            __threadErrno = 0;
-            ret = MoveFileW(_oldPathW, _newPathW);
-        } while ((ret == 0) && (__threadErrno == EINTR));
-        __END_INTERRUPTABLE__
-        if (ret == 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-            RETURN(false);
-        }
+	do {
+	    __threadErrno = 0;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = STX_API_NOINT_CALL2( "MoveFileW", MoveFileW, _oldPathW, _newPathW);
+	} while ((ret == 0) && (__threadErrno == EINTR));
+#else
+	__BEGIN_INTERRUPTABLE__
+	do {
+	    __threadErrno = 0;
+	    ret = MoveFileW(_oldPathW, _newPathW);
+	} while ((ret == 0) && (__threadErrno == EINTR));
+	__END_INTERRUPTABLE__
+	if (ret == 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	    RETURN(false);
+	}
 #endif
     }
     if (ret == 0) {
-        @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-        RETURN (false);
+	@global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	RETURN (false);
     }
     RETURN (true);
 
@@ -5214,43 +5053,43 @@
 #   endif
 
     if (aSymbol == @symbol(readUser)) {
-        RETURN ( __mkSmallInteger(S_IRUSR) );
+	RETURN ( __mkSmallInteger(S_IRUSR) );
     }
     if (aSymbol == @symbol(writeUser)) {
-        RETURN ( __mkSmallInteger(S_IWUSR) );
+	RETURN ( __mkSmallInteger(S_IWUSR) );
     }
     if (aSymbol == @symbol(executeUser)) {
-        RETURN ( __mkSmallInteger(S_IXUSR) );
+	RETURN ( __mkSmallInteger(S_IXUSR) );
     }
     if (aSymbol == @symbol(readGroup)) {
-        RETURN ( __mkSmallInteger(S_IRGRP) );
+	RETURN ( __mkSmallInteger(S_IRGRP) );
     }
     if (aSymbol == @symbol(writeGroup)) {
-        RETURN ( __mkSmallInteger(S_IWGRP) );
+	RETURN ( __mkSmallInteger(S_IWGRP) );
     }
     if (aSymbol == @symbol(executeGroup)) {
-        RETURN ( __mkSmallInteger(S_IXGRP) );
+	RETURN ( __mkSmallInteger(S_IXGRP) );
     }
     if (aSymbol == @symbol(readOthers)) {
-        RETURN ( __mkSmallInteger(S_IROTH) );
+	RETURN ( __mkSmallInteger(S_IROTH) );
     }
     if (aSymbol == @symbol(writeOthers)) {
-        RETURN ( __mkSmallInteger(S_IWOTH) );
+	RETURN ( __mkSmallInteger(S_IWOTH) );
     }
     if (aSymbol == @symbol(executeOthers)) {
-        RETURN ( __mkSmallInteger(S_IXOTH) );
+	RETURN ( __mkSmallInteger(S_IXOTH) );
     }
 
     // These are not defined for Win32 - simply ignore them
     // (but handle them for UNIX compatibility
     if (aSymbol == @symbol(setUid)) {
-        RETURN ( __mkSmallInteger(0) );
+	RETURN ( __mkSmallInteger(0) );
     }
     if (aSymbol == @symbol(setGid)) {
-        RETURN ( __mkSmallInteger(0) );
+	RETURN ( __mkSmallInteger(0) );
     }
     if (aSymbol == @symbol(removeOnlyByOwner)) {
-        RETURN ( __mkSmallInteger(0) );
+	RETURN ( __mkSmallInteger(0) );
     }
 
 %}.
@@ -5269,7 +5108,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
     "
 
@@ -5279,58 +5118,58 @@
 
     if (__isStringLike(aPathName)) {
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            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;
+	    // do not cast to INT - will loose sign bit then!
+	    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) );
     } else if (__isUnicode16String(aPathName)) {
 #ifdef DO_WRAP_CALLS
-        char _wPathName[MAXPATHLEN];
-
-        _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
-
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = STX_C_NOINT_CALL2( "_wstat", _wstat, _wPathName, &buf);
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        __BEGIN_INTERRUPTABLE__
-        do {
-            __threadErrno = 0;
-            ret = _wstat((char *)__unicode16StringVal(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 _wPathName[MAXPATHLEN];
+
+	_makeWchar(aPathName, _wPathName, sizeof(_wPathName));
+
+	do {
+	    __threadErrno = 0;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = STX_C_NOINT_CALL2( "_wstat", _wstat, _wPathName, &buf);
+	} while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	__BEGIN_INTERRUPTABLE__
+	do {
+	    __threadErrno = 0;
+	    ret = _wstat((char *)__unicode16StringVal(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
@@ -5351,7 +5190,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
     "
 
@@ -5361,39 +5200,39 @@
 
     if (__isSmallInteger(aFileDescriptor)) {
 #ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = STX_C_NOINT_CALL2( "fstat", fstat, __smallIntegerVal(aFileDescriptor), &buf);
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        __BEGIN_INTERRUPTABLE__
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = fstat( __smallIntegerVal(aFileDescriptor), &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) );
+	do {
+	    __threadErrno = 0;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = STX_C_NOINT_CALL2( "fstat", fstat, __smallIntegerVal(aFileDescriptor), &buf);
+	} while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	__BEGIN_INTERRUPTABLE__
+	do {
+	    __threadErrno = 0;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = fstat( __smallIntegerVal(aFileDescriptor), &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
 
    "
     'c:\windows' asFilename readingFileDo:[:s|
-        (OperatingSystem accessModeOfFd:s fileDescriptor) printStringRadix:8.
+	(OperatingSystem accessModeOfFd:s fileDescriptor) printStringRadix:8.
     ].
     'Make.proto' asFilename readingFileDo:[:s|
-        (OperatingSystem accessModeOfFd:s fileDescriptor) printStringRadix:8.
+	(OperatingSystem accessModeOfFd:s fileDescriptor) printStringRadix:8.
     ].
     (OperatingSystem changeAccessModeOf:'Make.proto' to:8r644)
    "
@@ -5409,62 +5248,62 @@
     int ret;
 
     if (__isSmallInteger(modeBits)) {
-        if (__isStringLike(aPathName)) {
+	if (__isStringLike(aPathName)) {
 #ifdef DO_WRAP_CALLS
-            int _chmod();
-            char _aPathName[MAXPATHLEN];
-
-            strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-            do {
-                __threadErrno = 0;
-                // do not cast to INT - will loose sign bit then!
-                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 );
-
-        } else if (__isUnicode16String(aPathName)) {
+	    int _chmod();
+	    char _aPathName[MAXPATHLEN];
+
+	    strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	    do {
+		__threadErrno = 0;
+		// do not cast to INT - will loose sign bit then!
+		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 );
+
+	} else if (__isUnicode16String(aPathName)) {
 #ifdef DO_WRAP_CALLS
-            int _wchmod();
-            char _wPathName[MAXPATHLEN];
-
-            _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
-            do {
-                __threadErrno = 0;
-                // do not cast to INT - will loose sign bit then!
-                ret = STX_C_NOINT_CALL2( "_wchmod", _wchmod, _wPathName, __intVal(modeBits));
-            } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-            __BEGIN_INTERRUPTABLE__
-            do {
-                __threadErrno = 0;
-                ret = _chmod((wchar_t *)__unicode16StringVal(fullPathName), __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 _wchmod();
+	    char _wPathName[MAXPATHLEN];
+
+	    _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
+	    do {
+		__threadErrno = 0;
+		// do not cast to INT - will loose sign bit then!
+		ret = STX_C_NOINT_CALL2( "_wchmod", _wchmod, _wPathName, __intVal(modeBits));
+	    } while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	    __BEGIN_INTERRUPTABLE__
+	    do {
+		__threadErrno = 0;
+		ret = _chmod((wchar_t *)__unicode16StringVal(fullPathName), __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:#argumentError
@@ -5498,14 +5337,14 @@
 
     if (__isExternalAddressLike(openFilenameStructureExternalAddress)
      || __isExternalBytesLike(openFilenameStructureExternalAddress)){
-        __address = __externalAddressVal(openFilenameStructureExternalAddress);
-        __rslt = __STX_API_CALL1( "GetOpenFileNameA", (void *)GetOpenFileNameA, __address);
-
-        if (__rslt == TRUE) {
-            rslt = true;
-        } else {
-            rslt = false;
-        }
+	__address = __externalAddressVal(openFilenameStructureExternalAddress);
+	__rslt = __STX_API_CALL1( "GetOpenFileNameA", (void *)GetOpenFileNameA, __address);
+
+	if (__rslt == TRUE) {
+	    rslt = true;
+	} else {
+	    rslt = false;
+	}
     }
 %}.
     rslt isNil ifTrue:[ self primitiveFailed ].
@@ -5528,14 +5367,14 @@
 
     if (__isExternalAddressLike(openFilenameStructureExternalAddress)
      || __isExternalBytesLike(openFilenameStructureExternalAddress)){
-        __address = __externalAddressVal(openFilenameStructureExternalAddress);
-        __rslt = __STX_API_CALL1( "GetSaveFileName", (void *)GetSaveFileName, __address);
-
-        if (__rslt == TRUE) {
-            rslt = true;
-        } else {
-            rslt = false;
-        }
+	__address = __externalAddressVal(openFilenameStructureExternalAddress);
+	__rslt = __STX_API_CALL1( "GetSaveFileName", (void *)GetSaveFileName, __address);
+
+	if (__rslt == TRUE) {
+	    rslt = true;
+	} else {
+	    rslt = false;
+	}
     }
 %}.
     rslt isNil ifTrue:[ self primitiveFailed ].
@@ -5561,7 +5400,7 @@
 
     attr := self primGetFileAttributes:aPathName.
     (attr bitTest:FILE_ATTRIBUTE_HIDDEN ) ifTrue:[
-        ^ self primSetFileAttributes:aPathName to:(attr bitClear:2).
+	^ self primSetFileAttributes:aPathName to:(attr bitClear:2).
     ].
     ^ true
 
@@ -5577,27 +5416,27 @@
     |names n "{ Class: SmallInteger }" |
 
     names := pathName
-                asCollectionOfSubstringsSeparatedBy:self fileSeparator.
+		asCollectionOfSubstringsSeparatedBy:self fileSeparator.
     names := names asOrderedCollection.
     "
      cut off initial double-slashes
     "
     [names startsWith:#('' '')] whileTrue:[
-        names removeFirst.
+	names removeFirst.
     ].
     "
      cut off double-slashes at end
     "
     [names endsWith:#('')] whileTrue:[
-        names removeLast.
+	names removeLast.
     ].
     "
      cut off current-dir at beginning
     "
     n := names size.
     [(n >= 2) and:[names startsWith:#('.')]] whileTrue:[
-        names removeFirst.
-        n := n - 1.
+	names removeFirst.
+	n := n - 1.
     ].
 
     "
@@ -5606,14 +5445,14 @@
     [(n > 2)
      and:[(names endsWith:#('..'))
      and:[((names at:(n - 1)) startsWith:'.') not ]]] whileTrue:[
-        names removeLast; removeLast.
-        n := n - 2.
+	names removeLast; removeLast.
+	n := n - 2.
     ].
 
     ^ names asStringWith:self fileSeparator
-                    from:1
-                    to:n
-                    compressTabs:false final:nil
+		    from:1
+		    to:n
+		    compressTabs:false final:nil
 
     "
      OperatingSystem compressPath:'.\..'
@@ -5636,6 +5475,80 @@
     ^ $\
 !
 
+getBinaryType:aPathName
+    "determines whether a file is executable.
+     Returns nil if not, or some symbol describing the type of
+     binary otherwise."
+
+%{
+// the following is 'not-yet-known' in borland
+#ifndef SCS_64BIT_BINARY
+# define SCS_64BIT_BINARY 6
+    // SCS_32BIT_BINARY = 0, // A 32-bit Windows-based application
+    // SCS_64BIT_BINARY = 6, // A 64-bit Windows-based application.
+    // SCS_DOS_BINARY = 1, // An MS-DOS – based application
+    // SCS_OS216_BINARY = 5, // A 16-bit OS/2-based application
+    // SCS_PIF_BINARY = 3, // A PIF file that executes an MS-DOS – based application
+    // SCS_POSIX_BINARY = 4, // A POSIX – based application
+    // SCS_WOW_BINARY = 2 // A 16-bit Windows-based application
+#endif
+
+    BOOL ok;
+    DWORD binaryType;
+
+    if (__isStringLike(aPathName)) {
+	ok = GetBinaryTypeA(__stringVal(aPathName), &binaryType);
+    } else if (__isUnicode16String(aPathName)) {
+	ok = GetBinaryTypeW(__unicode16StringVal(aPathName), &binaryType);
+    } else {
+	goto badArgument;
+    }
+
+    if (ok) {
+	OBJ typeSymbol = nil;
+
+	switch (binaryType) {
+	    case SCS_32BIT_BINARY:
+		// A 32bit Windows-based application
+		typeSymbol = @symbol(BINARY_32BIT);
+		break;
+	    case SCS_64BIT_BINARY:
+		// A 64bit Windows-based application.
+		typeSymbol = @symbol(BINARY_64BIT);
+		break;
+	    case SCS_DOS_BINARY:
+		// An MSDOS based application
+		typeSymbol = @symbol(BINARY_DOS);
+		break;
+	    case SCS_OS216_BINARY:
+		// A 16bit OS/2-based application
+		typeSymbol = @symbol(BINARY_OS2_16BIT);
+		break;
+	    case SCS_PIF_BINARY:
+		// A PIF file that executes an MS-DOS – based application
+		typeSymbol = @symbol(BINARY_PIF);
+		break;
+	    case SCS_POSIX_BINARY:
+		// A POSIX based application
+		typeSymbol = @symbol(BINARY_POSIX);
+		break;
+	    case SCS_WOW_BINARY:
+		// A 16-bit Windows-based application
+		typeSymbol = @symbol(BINARY_WOW16);
+		break;
+	    default:
+		typeSymbol = @symbol(other);
+		break;
+	}
+	RETURN (typeSymbol);
+    }
+    RETURN (nil);
+
+badArgument: ;
+%}.
+    self primitiveFailed
+!
+
 getCurrentDirectory
     "get the current directory"
 
@@ -5645,7 +5558,7 @@
 
     ret = GetCurrentDirectoryW(MAXPATHLEN, _aPathName);
     if (ret == 0) {
-        __threadErrno = __WIN32_ERR(GetLastError());
+	__threadErrno = __WIN32_ERR(GetLastError());
     }
     RETURN(__mkStringOrU16String_maxlen(_aPathName, MAXPATHLEN));
 %}.
@@ -5657,8 +5570,8 @@
 
 getDiskInfoOf:volumeNameArg
     "returns a dictionary filled with any of:
-        freeBytes
-        totalBytes
+	freeBytes
+	totalBytes
      and possibly additional (OS-specific) information"
 
     |volumeName info ok sectorsPerCluster bytesPerSector freeClusters totalClusters
@@ -5666,11 +5579,11 @@
 
     volumeName := volumeNameArg.
     (volumeName endsWith:$\) ifFalse:[
-        volumeName := volumeName , '\'
+	volumeName := volumeName , '\'
     ].
 %{
     typedef BOOL (WINAPI *P_GDFSE)(LPCTSTR, PULARGE_INTEGER,
-                                   PULARGE_INTEGER, PULARGE_INTEGER);
+				   PULARGE_INTEGER, PULARGE_INTEGER);
     P_GDFSE pGetDiskFreeSpaceEx = NULL;
 
     DWORD __sectorsPerCluster, __bytesPerSector, __freeClusters, __totalClusters;
@@ -5678,62 +5591,62 @@
     unsigned __int64 i64FreeBytesForUsersQuota, i64TotalBytes, i64FreeBytes;
 
     if (__isStringLike(volumeName) || __isSymbol(volumeName)) {
-         /*
-          *  Use GetDiskFreeSpaceEx if available; otherwise, use GetDiskFreeSpace.
-          *  Notice that GetDiskFreeSpace does not work correctly under win2k,
-          *  and GetDiskFreeSpaceEx is not avail. for all win versions (can microsoft ever do something right ?).
-          */
-        pGetDiskFreeSpaceEx = (P_GDFSE)GetProcAddress (
-                                            GetModuleHandle ("kernel32.dll"),
-                                                             "GetDiskFreeSpaceExA");
-        if (pGetDiskFreeSpaceEx) {
-            fResult = pGetDiskFreeSpaceEx (__stringVal(volumeName),
-                                 (PULARGE_INTEGER)&i64FreeBytesForUsersQuota,
-                                 (PULARGE_INTEGER)&i64TotalBytes,
-                                 (PULARGE_INTEGER)&i64FreeBytes);
-            if (fResult) {
-                freeBytesForUsersQuota = __MKUINT64(&i64FreeBytesForUsersQuota);
-                totalBytes = __MKUINT64(&i64TotalBytes);
-                freeBytes = __MKUINT64(&i64FreeBytes);
-            }
-        }
-        fResult = GetDiskFreeSpace(__stringVal(volumeName),
-                             &__sectorsPerCluster,
-                             &__bytesPerSector,
-                             &__freeClusters,
-                             &__totalClusters);
-        if (fResult) {
-            sectorsPerCluster = __MKUINT(__sectorsPerCluster);
-            bytesPerSector = __MKUINT(__bytesPerSector);
-            freeClusters = __MKUINT(__freeClusters);
-            totalClusters = __MKUINT(__totalClusters);
-        }
-        switch (GetDriveType(__stringVal(volumeName))) {
-            case DRIVE_REMOVABLE:
-                type = @symbol(removable); break;
-            case DRIVE_FIXED:
-                type = @symbol(fixed); break;
-            case DRIVE_REMOTE:
-                type = @symbol(network); break;
-            case DRIVE_CDROM:
-                type = @symbol(cdrom); break;
-            case DRIVE_RAMDISK:
-                type = @symbol(ramdisk); break;
-            case DRIVE_UNKNOWN:
-            default:
-                break;
-        }
-        if (fResult) {
-            ok = true;
-        } else {
-            __threadErrno = __WIN32_ERR(GetLastError());
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-        }
+	 /*
+	  *  Use GetDiskFreeSpaceEx if available; otherwise, use GetDiskFreeSpace.
+	  *  Notice that GetDiskFreeSpace does not work correctly under win2k,
+	  *  and GetDiskFreeSpaceEx is not avail. for all win versions (can microsoft ever do something right ?).
+	  */
+	pGetDiskFreeSpaceEx = (P_GDFSE)GetProcAddress (
+					    GetModuleHandle ("kernel32.dll"),
+							     "GetDiskFreeSpaceExA");
+	if (pGetDiskFreeSpaceEx) {
+	    fResult = pGetDiskFreeSpaceEx (__stringVal(volumeName),
+				 (PULARGE_INTEGER)&i64FreeBytesForUsersQuota,
+				 (PULARGE_INTEGER)&i64TotalBytes,
+				 (PULARGE_INTEGER)&i64FreeBytes);
+	    if (fResult) {
+		freeBytesForUsersQuota = __MKUINT64(&i64FreeBytesForUsersQuota);
+		totalBytes = __MKUINT64(&i64TotalBytes);
+		freeBytes = __MKUINT64(&i64FreeBytes);
+	    }
+	}
+	fResult = GetDiskFreeSpace(__stringVal(volumeName),
+			     &__sectorsPerCluster,
+			     &__bytesPerSector,
+			     &__freeClusters,
+			     &__totalClusters);
+	if (fResult) {
+	    sectorsPerCluster = __MKUINT(__sectorsPerCluster);
+	    bytesPerSector = __MKUINT(__bytesPerSector);
+	    freeClusters = __MKUINT(__freeClusters);
+	    totalClusters = __MKUINT(__totalClusters);
+	}
+	switch (GetDriveType(__stringVal(volumeName))) {
+	    case DRIVE_REMOVABLE:
+		type = @symbol(removable); break;
+	    case DRIVE_FIXED:
+		type = @symbol(fixed); break;
+	    case DRIVE_REMOTE:
+		type = @symbol(network); break;
+	    case DRIVE_CDROM:
+		type = @symbol(cdrom); break;
+	    case DRIVE_RAMDISK:
+		type = @symbol(ramdisk); break;
+	    case DRIVE_UNKNOWN:
+	    default:
+		break;
+	}
+	if (fResult) {
+	    ok = true;
+	} else {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	    @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+	}
     }
 %}.
     ok == true ifFalse:[
-        self primitiveFailed.
-        ^ self
+	self primitiveFailed.
+	^ self
     ].
 
     info := IdentityDictionary new.
@@ -5743,14 +5656,14 @@
     info at:#totalClusters put:totalClusters.
 
     info at:#freeBytes put:(freeBytes notNil
-                                ifTrue:[freeBytes]
-                                ifFalse:[freeClusters * sectorsPerCluster * bytesPerSector]).
+				ifTrue:[freeBytes]
+				ifFalse:[freeClusters * sectorsPerCluster * bytesPerSector]).
     info at:#totalBytes put:(totalBytes notNil
-                                ifTrue:[totalBytes]
-                                ifFalse:[totalClusters * sectorsPerCluster * bytesPerSector]).
+				ifTrue:[totalBytes]
+				ifFalse:[totalClusters * sectorsPerCluster * bytesPerSector]).
     info at:#freeBytesForUsersQuota put:freeBytesForUsersQuota.
     type notNil ifTrue:[
-        info at:#type put:type
+	info at:#type put:type
     ].
     ^ info
 
@@ -5792,13 +5705,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."
 
 %{
@@ -5807,18 +5720,18 @@
 
     if (_makeWchar(aPathName, _aPathName, sizeof(_aPathName)) > 0) {
 #ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = (int)(STX_API_NOINT_CALL1( "GetDriveTypeW", GetDriveTypeW, _aPathName));
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        ret = GetDriveTypeW(_aPathName);
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        RETURN (__MKSMALLINT(ret));
+	do {
+	    __threadErrno = 0;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = (int)(STX_API_NOINT_CALL1( "GetDriveTypeW", GetDriveTypeW, _aPathName));
+	} while ((ret < 0) && (__threadErrno == EINTR));
+#else
+	ret = GetDriveTypeW(_aPathName);
+	if (ret < 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
+#endif
+	RETURN (__MKSMALLINT(ret));
     }
 %}.
     ^ self primitiveFailed
@@ -5841,24 +5754,24 @@
     DWORD dummy;
 
     if (__isStringLike(aPathName)) {
-        sz = GetFileVersionInfoSizeA(__stringVal(aPathName), &dummy);
+	sz = GetFileVersionInfoSizeA(__stringVal(aPathName), &dummy);
     } else if (__isUnicode16String(aPathName)) {
-        sz = GetFileVersionInfoSizeW(__unicode16StringVal(aPathName), &dummy);
+	sz = GetFileVersionInfoSizeW(__unicode16StringVal(aPathName), &dummy);
     } else {
-        goto badArgument;
+	goto badArgument;
     }
 
     if (sz > 0) {
-        OBJ versionData;
-
-        versionData = __BYTEARRAY_UNINITIALIZED_NEW_INT(sz);
-        if (versionData == nil) {
-            RETURN (nil);
-        }
-        if (GetFileVersionInfo(__stringVal(aPathName), 0, sz, __ByteArrayInstPtr(versionData)->ba_element) == FALSE) {
-            RETURN (nil);
-        }
-        RETURN (versionData);
+	OBJ versionData;
+
+	versionData = __BYTEARRAY_UNINITIALIZED_NEW_INT(sz);
+	if (versionData == nil) {
+	    RETURN (nil);
+	}
+	if (GetFileVersionInfo(__stringVal(aPathName), 0, sz, __ByteArrayInstPtr(versionData)->ba_element) == FALSE) {
+	    RETURN (nil);
+	}
+	RETURN (versionData);
     }
     RETURN (nil);
 badArgument: ;
@@ -5877,18 +5790,18 @@
 
     if (_makeWchar(aPathName, _aPathName, sizeof(_aPathName)) > 0) {
 #ifdef DO_WRAP_CALLS
-         do {
-             __threadErrno = 0;
-             // do not cast to INT - will loose sign bit then!
-             ret = (int)(STX_API_NOINT_CALL3( "GetLongPathNameW", GetLongPathNameW, _aPathName, _aPathName, MAXPATHLEN));
-         } while ((ret == 0) && (__threadErrno == EINTR));
-#else
-         ret = GetLongPathNameW(_aPathName, _aPathName, MAXPATHLEN);
-         if (ret == 0) {
-             __threadErrno = __WIN32_ERR(GetLastError());
-         }
-#endif
-         RETURN (__mkStringOrU16String_maxlen(_aPathName, MAXPATHLEN));
+	 do {
+	     __threadErrno = 0;
+	     // do not cast to INT - will loose sign bit then!
+	     ret = (int)(STX_API_NOINT_CALL3( "GetLongPathNameW", GetLongPathNameW, _aPathName, _aPathName, MAXPATHLEN));
+	 } while ((ret == 0) && (__threadErrno == EINTR));
+#else
+	 ret = GetLongPathNameW(_aPathName, _aPathName, MAXPATHLEN);
+	 if (ret == 0) {
+	     __threadErrno = __WIN32_ERR(GetLastError());
+	 }
+#endif
+	 RETURN (__mkStringOrU16String_maxlen(_aPathName, MAXPATHLEN));
     }
 %}.
     ^ self primitiveFailed
@@ -5913,9 +5826,9 @@
 
      The info object returned is OS-specific, however it responds to at
      least
-        #isFor32BitArchitecture
-        #isFor64BitArchitecture ... returns true, if the given object is for
-                                     32bit, 64bit architecture respectively
+	#isFor32BitArchitecture
+	#isFor64BitArchitecture ... returns true, if the given object is for
+				     32bit, 64bit architecture respectively
     "
     ^ PECOFFFileHeader fromFile: aStringOrFilename
 
@@ -5931,18 +5844,18 @@
 
     if (_makeWchar(aPathName, _aPathName, sizeof(_aPathName)) > 0) {
 #ifdef DO_WRAP_CALLS
-         do {
-             __threadErrno = 0;
-             // do not cast to INT - will loose sign bit then!
-             ret = (int)(STX_API_NOINT_CALL3( "GetShortPathNameW", GetShortPathNameW, _aPathName, _aPathName, MAXPATHLEN));
-         } while ((ret == 0) && (__threadErrno == EINTR));
-#else
-         ret = GetShortPathNameW(_aPathName, _aPathName, MAXPATHLEN);
-         if (ret == 0) {
-             __threadErrno = __WIN32_ERR(GetLastError());
-         }
-#endif
-         RETURN (__mkStringOrU16String_maxlen(_aPathName, MAXPATHLEN));
+	 do {
+	     __threadErrno = 0;
+	     // do not cast to INT - will loose sign bit then!
+	     ret = (int)(STX_API_NOINT_CALL3( "GetShortPathNameW", GetShortPathNameW, _aPathName, _aPathName, MAXPATHLEN));
+	 } while ((ret == 0) && (__threadErrno == EINTR));
+#else
+	 ret = GetShortPathNameW(_aPathName, _aPathName, MAXPATHLEN);
+	 if (ret == 0) {
+	     __threadErrno = __WIN32_ERR(GetLastError());
+	 }
+#endif
+	 RETURN (__mkStringOrU16String_maxlen(_aPathName, MAXPATHLEN));
      }
 %}.
     ^ self primitiveFailed
@@ -5971,16 +5884,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.
@@ -5994,10 +5907,10 @@
 
     info := self linkInfoOf:aPathName.
     (info notNil and:[info isSymbolicLink]) ifTrue:[
-        target := info path.
-        target notNil ifTrue:[
-            ^ self linkInfoOf:target.
-        ]
+	target := info path.
+	target notNil ifTrue:[
+	    ^ self linkInfoOf:target.
+	]
     ].
     ^ info
 
@@ -6022,42 +5935,42 @@
 
     if (__isStringLike(aPathName)) {
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = (int)(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;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = (int)(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];
-
-        _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
+	wchar_t _wPathName[MAXPATHLEN+1];
+
+	_makeWchar(aPathName, _wPathName, sizeof(_wPathName));
 #ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = (int)(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;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = (int)(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:;
@@ -6065,7 +5978,7 @@
     ^ self primitiveFailed
 
     "an alternative implementation would be:
-        ^ (self infoOf:aPathName) type == #directory
+	^ (self infoOf:aPathName) type == #directory
     "
     "
      self isDirectory:'.'
@@ -6153,8 +6066,8 @@
 
     attr := self primGetFileAttributes:aPathName.
     attr notNil ifTrue:[
-        ^ (attr bitAnd: (FILE_ATTRIBUTE_DIRECTORY bitOr: FILE_ATTRIBUTE_READONLY ))
-            ~~ FILE_ATTRIBUTE_READONLY
+	^ (attr bitAnd: (FILE_ATTRIBUTE_DIRECTORY bitOr: FILE_ATTRIBUTE_READONLY ))
+	    ~~ FILE_ATTRIBUTE_READONLY
     ].
     ^ false
 
@@ -6169,16 +6082,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.
@@ -6205,28 +6118,28 @@
     wchar_t _wPathName[MAXPATHLEN+1];
 
     if (_makeWchar(aPathName, _wPathName, sizeof(_wPathName)) < 0)
-        goto badArgument;
+	goto badArgument;
 
 #ifdef DO_WRAP_CALLS
     {
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            result = (int)(STX_API_NOINT_CALL3( "GetFileAttributesExW", GetFileAttributesExW, _wPathName, GetFileExInfoStandard, &fileAttributeData));
-        } while (!result && (__threadErrno == EINTR));
+	do {
+	    __threadErrno = 0;
+	    // do not cast to INT - will loose sign bit then!
+	    result = (int)(STX_API_NOINT_CALL3( "GetFileAttributesExW", GetFileAttributesExW, _wPathName, GetFileExInfoStandard, &fileAttributeData));
+	} while (!result && (__threadErrno == EINTR));
     }
 #else
     result = GetFileAttributesExW(_wPathName, 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, MAXPATHLEN*sizeof(wchar_t));
@@ -6240,79 +6153,79 @@
 //            alternativeName = __mkStringOrU16String_maxlen(alternativeFileNameBuffer, 14); /* 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 = FileTimeToOsTime1970(&fileAttributeData.ftCreationTime);
-        aOsTime = FileTimeToOsTime1970(&fileAttributeData.ftLastAccessTime);
-        mOsTime = FileTimeToOsTime1970(&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 = FileTimeToOsTime1970(&fileAttributeData.ftCreationTime);
+	aOsTime = FileTimeToOsTime1970(&fileAttributeData.ftLastAccessTime);
+	mOsTime = FileTimeToOsTime1970(&fileAttributeData.ftLastWriteTime);
     }
 
   badArgument: ;
 %}.
 
     (aPathName endsWith:'.lnk') ifTrue:[
-        type := #symbolicLink.
-        "/ now done lazily in FileStatusInfo, when the path is accessed
-        "/ path := self getLinkTarget:aPathName.
+	type := #symbolicLink.
+	"/ now done lazily 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:[
-            "/ rebias to 1970 by subtracting the number of millis from 1.1.1601 to 1.1.1970
-            "/ aOsTime := aOsTime - self osTimeOf19700101. -- already done
-            atime := Timestamp new fromOSTime:aOsTime.
-        ].
-        mtime isNil ifTrue:[
-            "/ rebias to 1970 by subtracting the number of millis from 1.1.1601 to 1.1.1970
-            "/ mOsTime := mOsTime - self osTimeOf19700101. -- already done
-            mtime := Timestamp new fromOSTime:mOsTime.
-        ].
-        ctime isNil ifTrue:[
-            "/ rebias to 1970 by subtracting the number of millis from 1.1.1601 to 1.1.1970
-            "/ cOsTime := cOsTime - self osTimeOf19700101. -- already done
-            ctime := Timestamp new fromOSTime:cOsTime.
-        ].
-
-        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:[
+	    "/ rebias to 1970 by subtracting the number of millis from 1.1.1601 to 1.1.1970
+	    "/ aOsTime := aOsTime - self osTimeOf19700101. -- already done
+	    atime := Timestamp new fromOSTime:aOsTime.
+	].
+	mtime isNil ifTrue:[
+	    "/ rebias to 1970 by subtracting the number of millis from 1.1.1601 to 1.1.1970
+	    "/ mOsTime := mOsTime - self osTimeOf19700101. -- already done
+	    mtime := Timestamp new fromOSTime:mOsTime.
+	].
+	ctime isNil ifTrue:[
+	    "/ rebias to 1970 by subtracting the number of millis from 1.1.1601 to 1.1.1970
+	    "/ cOsTime := cOsTime - self osTimeOf19700101. -- already done
+	    ctime := Timestamp new fromOSTime:cOsTime.
+	].
+
+	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
 
@@ -6333,8 +6246,8 @@
      Returns nil if no mimeType for the given suffix is known."
 
     ^ RegistryEntry
-        stringValueFor:'Content Type'
-        atKey:('HKEY_CLASSES_ROOT\.' , aFileSuffix)
+	stringValueFor:'Content Type'
+	atKey:('HKEY_CLASSES_ROOT\.' , aFileSuffix)
 
     "
      self mimeTypeForSuffix:'au'
@@ -6367,20 +6280,20 @@
     path := self primPathNameOf:pathName.
 
     path isNil ifTrue:[
-        (self isValidPath:pathName) ifFalse:[
-            p := pathName.
-            [(p size > 1)
-             and:[p endsWith:(self fileSeparator)]
-            ] whileTrue:[
-                p := p copyButLast:1.
-            ].
-            ^ p
-        ].
-
-        "/
-        "/ return the original - there is nothing else can we do
-        "/
-        path := self compressPath:pathName
+	(self isValidPath:pathName) ifFalse:[
+	    p := pathName.
+	    [(p size > 1)
+	     and:[p endsWith:(self fileSeparator)]
+	    ] whileTrue:[
+		p := p copyButLast:1.
+	    ].
+	    ^ p
+	].
+
+	"/
+	"/ return the original - there is nothing else can we do
+	"/
+	path := self compressPath:pathName
     ].
     ^ path.
 
@@ -6409,54 +6322,54 @@
 
     if (__isStringLike(aPathName)) {
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = (int)(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;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = (int)(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];
-
-        _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
+	wchar_t _wPathName[MAXPATHLEN+1];
+
+	_makeWchar(aPathName, _wPathName, sizeof(_wPathName));
 
 #ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = (int)(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;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = (int)(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);
     }
 %}.
     (aPathName isString and:[aPathName isUnicode32String]) ifTrue:[
-        "/ WIN32 only support 16 bit (wide) strings
-        ^ self primGetFileAttributes:aPathName asUnicode16String
+	"/ WIN32 only support 16 bit (wide) strings
+	^ self primGetFileAttributes:aPathName asUnicode16String
     ].
 
     ^ self primitiveFailed
@@ -6488,86 +6401,86 @@
 
 %{
     if (__isStringLike(aPathName)) {
-        char nameBuffer[MAXPATHLEN + 1];
-        char nameBuffer2[MAXPATHLEN + 1];
-        char *returnedName = NULL;
-        int rslt;
+	char nameBuffer[MAXPATHLEN + 1];
+	char nameBuffer2[MAXPATHLEN + 1];
+	char *returnedName = NULL;
+	int rslt;
 
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN+1];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            rslt = (int)(STX_API_NOINT_CALL4( "GetFullPathNameA", GetFullPathNameA, _aPathName, MAXPATHLEN, nameBuffer, NULL));
-        } while ((rslt < 0) && (__threadErrno == EINTR));
-#else
-        rslt = GetFullPathNameA(__stringVal(aPathName), MAXPATHLEN, nameBuffer, NULL);
-#endif
-        returnedName = nameBuffer;
-
-        if (rslt > 0) {
+	char _aPathName[MAXPATHLEN+1];
+
+	strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	do {
+	    __threadErrno = 0;
+	    // do not cast to INT - will loose sign bit then!
+	    rslt = (int)(STX_API_NOINT_CALL4( "GetFullPathNameA", GetFullPathNameA, _aPathName, MAXPATHLEN, nameBuffer, NULL));
+	} while ((rslt < 0) && (__threadErrno == EINTR));
+#else
+	rslt = GetFullPathNameA(__stringVal(aPathName), MAXPATHLEN, nameBuffer, NULL);
+#endif
+	returnedName = nameBuffer;
+
+	if (rslt > 0) {
 #ifdef DO_WRAP_CALLS
-            do {
-                __threadErrno = 0;
-                // do not cast to INT - will loose sign bit then!
-                rslt = (int)(STX_API_NOINT_CALL3( "GetLongPathNameA", GetLongPathNameA, nameBuffer, nameBuffer2, MAXPATHLEN));
-            } while ((rslt < 0) && (__threadErrno == EINTR));
-#else
-            rslt = GetLongPathNameA(nameBuffer, nameBuffer2, MAXPATHLEN);
-#endif
-            returnedName = nameBuffer2;
-        }
-        if (rslt > 0) {
-            RETURN ( __MKSTRING(returnedName) );
-        }
-        __threadErrno = __WIN32_ERR(GetLastError());
-        RETURN (nil);
+	    do {
+		__threadErrno = 0;
+		// do not cast to INT - will loose sign bit then!
+		rslt = (int)(STX_API_NOINT_CALL3( "GetLongPathNameA", GetLongPathNameA, nameBuffer, nameBuffer2, MAXPATHLEN));
+	    } while ((rslt < 0) && (__threadErrno == EINTR));
+#else
+	    rslt = GetLongPathNameA(nameBuffer, nameBuffer2, MAXPATHLEN);
+#endif
+	    returnedName = nameBuffer2;
+	}
+	if (rslt > 0) {
+	    RETURN ( __MKSTRING(returnedName) );
+	}
+	__threadErrno = __WIN32_ERR(GetLastError());
+	RETURN (nil);
     }
     if (__isUnicode16String(aPathName)) {
-        wchar_t nameBuffer[MAXPATHLEN + 1];
-        wchar_t nameBuffer2[MAXPATHLEN + 1];
-        wchar_t *returnedName = NULL;
-        int rslt;
-        wchar_t _wPathName[MAXPATHLEN+1];
-
-        _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
+	wchar_t nameBuffer[MAXPATHLEN + 1];
+	wchar_t nameBuffer2[MAXPATHLEN + 1];
+	wchar_t *returnedName = NULL;
+	int rslt;
+	wchar_t _wPathName[MAXPATHLEN+1];
+
+	_makeWchar(aPathName, _wPathName, sizeof(_wPathName));
 
 #ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            rslt = (int)(STX_API_NOINT_CALL4( "GetFullPathNameW", GetFullPathNameW, _wPathName, MAXPATHLEN, nameBuffer, NULL));
-        } while ((rslt < 0) && (__threadErrno == EINTR));
-#else
-        rslt = GetFullPathNameW(_wPathName, MAXPATHLEN, nameBuffer, NULL);
-#endif
-
-        returnedName = nameBuffer;
-
-        if (rslt > 0) {
+	do {
+	    __threadErrno = 0;
+	    rslt = (int)(STX_API_NOINT_CALL4( "GetFullPathNameW", GetFullPathNameW, _wPathName, MAXPATHLEN, nameBuffer, NULL));
+	} while ((rslt < 0) && (__threadErrno == EINTR));
+#else
+	rslt = GetFullPathNameW(_wPathName, MAXPATHLEN, nameBuffer, NULL);
+#endif
+
+	returnedName = nameBuffer;
+
+	if (rslt > 0) {
 
 #ifdef DO_WRAP_CALLS
-            do {
-                __threadErrno = 0;
-                rslt = (int)(STX_API_NOINT_CALL3( "GetLongPathNameW", GetLongPathNameW, nameBuffer, nameBuffer2, MAXPATHLEN));
-            } while ((rslt < 0) && (__threadErrno == EINTR));
-#else
-            rslt = GetLongPathNameW(nameBuffer, nameBuffer2, MAXPATHLEN);
-#endif
-            returnedName = nameBuffer2;
-        }
-        if (rslt > 0) {
-            RETURN (__mkStringOrU16String_maxlen(returnedName, MAXPATHLEN));
-        }
-        __threadErrno = __WIN32_ERR(GetLastError());
-        RETURN (nil);
+	    do {
+		__threadErrno = 0;
+		rslt = (int)(STX_API_NOINT_CALL3( "GetLongPathNameW", GetLongPathNameW, nameBuffer, nameBuffer2, MAXPATHLEN));
+	    } while ((rslt < 0) && (__threadErrno == EINTR));
+#else
+	    rslt = GetLongPathNameW(nameBuffer, nameBuffer2, MAXPATHLEN);
+#endif
+	    returnedName = nameBuffer2;
+	}
+	if (rslt > 0) {
+	    RETURN (__mkStringOrU16String_maxlen(returnedName, MAXPATHLEN));
+	}
+	__threadErrno = __WIN32_ERR(GetLastError());
+	RETURN (nil);
     }
     error = @symbol(argument);     // argument is not a string or unicode16string
 %}.
 
     error notNil ifTrue:[
-        self primitiveFailed:error.
+	self primitiveFailed:error.
     ].
     ^ nil
 
@@ -6605,51 +6518,51 @@
     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;
-                // do not cast to INT - will loose sign bit then!
-                ret = (int)(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];
-
-            _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
+	    char _aPathName[MAXPATHLEN];
+
+	    strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+	    do {
+		__threadErrno = 0;
+		// do not cast to INT - will loose sign bit then!
+		ret = (int)(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];
+
+	    _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
 #ifdef DO_WRAP_CALLS
-            do {
-                __threadErrno = 0;
-                // do not cast to INT - will loose sign bit then!
-                ret = (int)(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;
+		// do not cast to INT - will loose sign bit then!
+		ret = (int)(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
@@ -6657,9 +6570,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
     ].
 
     "
@@ -6677,7 +6590,7 @@
 
     attr := self primGetFileAttributes:aPathName.
     (attr bitTest:FILE_ATTRIBUTE_HIDDEN ) ifFalse:[
-        ^ self primSetFileAttributes:aPathName to:(attr bitOr:2).
+	^ self primSetFileAttributes:aPathName to:(attr bitOr:2).
     ].
     ^ true  "/ aready set
 
@@ -6692,7 +6605,7 @@
 
     attr := self primGetFileAttributes:aPathName.
     (attr bitTest:FILE_ATTRIBUTE_NORMAL ) ifFalse:[
-        ^ self primSetFileAttributes:aPathName to:(attr bitOr:2).
+	^ self primSetFileAttributes:aPathName to:(attr bitOr:2).
     ].
     ^ true  "/ aready set
 !
@@ -6704,7 +6617,7 @@
 
     attr := self primGetFileAttributes:aPathName.
     (attr bitTest:FILE_ATTRIBUTE_TEMPORARY ) ifFalse:[
-        ^ self primSetFileAttributes:aPathName to:(attr bitOr:2).
+	^ self primSetFileAttributes:aPathName to:(attr bitOr:2).
     ].
     ^ true  "/ aready set
 !
@@ -6714,7 +6627,7 @@
      For nonexistent files, nil is returned."
 
     "could be implemented as:
-        (self infoOf:aPathName) accessed
+	(self infoOf:aPathName) accessed
     "
     | i|
 
@@ -6732,7 +6645,7 @@
      For nonexistent files, nil is returned."
 
     "could be implemented as:
-        (self infoOf:aPathName) modified
+	(self infoOf:aPathName) modified
     "
 
     | i|
@@ -6755,7 +6668,7 @@
 
     "
      this could have been implemented as:
-        (self infoOf:aPathName) type
+	(self infoOf:aPathName) type
     "
 
     i := self infoOf:aPathName.
@@ -6772,31 +6685,31 @@
 
 volumeLabelOf: aFilenameOrString
 
-        "Answer the volume label of the disk containing aFilenameOrString."
+	"Answer the volume label of the disk containing aFilenameOrString."
 
     | volName |
 
     volName := String new: 255.
     ( self
-        getVolumeInformation: aFilenameOrString asFilename volume, '\'
-        name: volName
-        nameSize: volName size
-        serialNumber: nil
-        maximumComponentLength: nil
-        fileSystemFlags: nil
-        fileSystemName: nil
-        fileSystemNameSize: 0 )
-            ifFalse: [
-                Transcript showCR:'GetVolumeInformation error'.
-                ^ ''
-        ].
+	getVolumeInformation: aFilenameOrString asFilename volume, '\'
+	name: volName
+	nameSize: volName size
+	serialNumber: nil
+	maximumComponentLength: nil
+	fileSystemFlags: nil
+	fileSystemName: nil
+	fileSystemNameSize: 0 )
+	    ifFalse: [
+		Transcript showCR:'GetVolumeInformation error'.
+		^ ''
+	].
     ^ volName copyUpTo: Character null
 
     "
-        self volumeLabelOf: 'C:\pepe.pep'
-        self volumeLabelOf: 'C:'
-        self volumeLabelOf: 'C:\\'
-        self volumeLabelOf: 'C:\'
+	self volumeLabelOf: 'C:\pepe.pep'
+	self volumeLabelOf: 'C:'
+	self volumeLabelOf: 'C:\\'
+	self volumeLabelOf: 'C:\'
 
     "
 !
@@ -6809,7 +6722,7 @@
 
     aPathString size < 2 ifTrue:[^ ''].
     (aPathString at:2) == $: ifTrue:[
-        ^ (aPathString at:1) asString.
+	^ (aPathString at:1) asString.
     ].
     ^ ''
 ! !
@@ -6826,11 +6739,11 @@
      html documents, pdf documents etc."
 
     Error
-        handle:[:ex |
-            Dialog warn:'Shell execution failed'
-        ] do:[
-            self openApplicationForDocument:aFilenameOrString operation:#open
-        ]
+	handle:[:ex |
+	    Dialog warn:'Shell execution failed'
+	] do:[
+	    self openApplicationForDocument:aFilenameOrString operation:#open
+	]
 
     "
      self openDocumentationFilename: 'C:\WINDOWS\Help\clipbrd.chm' asFilename
@@ -6887,8 +6800,8 @@
 
 %{
     while(1) {
-        console_printf("blocking...");
-        Sleep(50);
+	console_printf("blocking...");
+	Sleep(50);
     }
 %}.
     "
@@ -6902,8 +6815,8 @@
 
 %{
     while(1) {
-        console_printf("blocking...");
-        STX_API_CALL1("Sleep", Sleep, 50);
+	console_printf("blocking...");
+	STX_API_CALL1("Sleep", Sleep, 50);
     }
 %}.
     "
@@ -6920,8 +6833,8 @@
     int ret;
 
     do {
-        // do not cast to INT - will loose sign bit then!
-        ret = (int)(STX_API_NOINT_CALL1("Sleep", Sleep, 60000));
+	// do not cast to INT - will loose sign bit then!
+	ret = (int)(STX_API_NOINT_CALL1("Sleep", Sleep, 60000));
     } while (ret < 0 && __threadErrno == EINTR);
 %}.
     "
@@ -6938,8 +6851,8 @@
     int ret;
 
     do {
-        // do not cast to INT - will loose sign bit then!
-        ret = STX_API_CALL1("Sleep", Sleep, 60000);
+	// do not cast to INT - will loose sign bit then!
+	ret = STX_API_CALL1("Sleep", Sleep, 60000);
     } while (ret < 0 && __threadErrno == EINTR);
 %}.
     "
@@ -6961,8 +6874,8 @@
 
     if (__isSmallInteger(signalNumber)) {
 #ifdef SIG_DFL
-        signal(__intVal(signalNumber), SIG_DFL);
-        RETURN (self);
+	signal(__intVal(signalNumber), SIG_DFL);
+	RETURN (self);
 #endif
     }
 %}.
@@ -7005,14 +6918,14 @@
 %{  /* NOCONTEXT */
 
     if (__isSmallInteger(signalNumber)) {
-        int sigNo = __intVal(signalNumber);
-
-        if (sigNo == 0) {
-            RETURN (self);
-        }
+	int sigNo = __intVal(signalNumber);
+
+	if (sigNo == 0) {
+	    RETURN (self);
+	}
 #ifdef SIG_IGN
-        signal(sigNo, SIG_IGN);
-        RETURN (self);
+	signal(sigNo, SIG_IGN);
+	RETURN (self);
 #endif
     }
 %}.
@@ -7033,8 +6946,8 @@
 disableTimer
     "disable timer interrupts.
      WARNING:
-        the system will not operate correctly with timer interrupts
-        disabled, because no scheduling or timeouts are possible."
+	the system will not operate correctly with timer interrupts
+	disabled, because no scheduling or timeouts are possible."
 
 %{  /* NOCONTEXT */
 
@@ -7157,121 +7070,121 @@
      &&  (sigNr <= SIG_LIMIT)
 #endif
     ) {
-        /*
-         * standard signals are forced into standard handlers
-         * - all others go into general signalInterrupt
-         */
+	/*
+	 * standard signals are forced into standard handlers
+	 * - all others go into general signalInterrupt
+	 */
 #if defined(SIGPOLL) && defined(SIGIO)
-        if (sigNr == SIGPOLL)
-            sigNr = SIGIO;
-#endif
-        switch (sigNr) {
-            case 0:
-                /* enabling a non-supported signal */
-                RETURN (self);
+	if (sigNr == SIGPOLL)
+	    sigNr = SIGIO;
+#endif
+	switch (sigNr) {
+	    case 0:
+		/* enabling a non-supported signal */
+		RETURN (self);
 
 #ifdef SIGBREAK
-            case SIGBREAK:
+	    case SIGBREAK:
 #endif
 #ifdef SIGINT
-            case SIGINT:
+	    case SIGINT:
 #endif
 #ifdef SIGQUIT
-            case SIGQUIT:
+	    case SIGQUIT:
 #endif
 #ifdef SIGNALDEBUGWIN32
-                console_printf("ConsoleSignal %d\n",sigNr);
-#endif
-                SetConsoleCtrlHandler((PHANDLER_ROUTINE)__signalUserInterruptWIN32,TRUE);
-                RETURN (self);
+		console_printf("ConsoleSignal %d\n",sigNr);
+#endif
+		SetConsoleCtrlHandler((PHANDLER_ROUTINE)__signalUserInterruptWIN32,TRUE);
+		RETURN (self);
 #ifdef SIGFPE
-            case SIGFPE:
-                handler = __signalFpExceptionInterrupt;
-                break;
+	    case SIGFPE:
+		handler = __signalFpExceptionInterrupt;
+		break;
 #endif
 
 #ifdef SIGPIPE
-            case SIGPIPE:
-                handler = __signalPIPEInterrupt;
-                break;
+	    case SIGPIPE:
+		handler = __signalPIPEInterrupt;
+		break;
 #endif
 #ifdef SIGBUS
-            case SIGBUS:
-                handler = __signalBUSInterrupt;
-                break;
+	    case SIGBUS:
+		handler = __signalBUSInterrupt;
+		break;
 #endif
 #ifdef SIGSEGV
-            case SIGSEGV:
-                handler = __signalSEGVInterrupt;
-                break;
+	    case SIGSEGV:
+		handler = __signalSEGVInterrupt;
+		break;
 #endif
 #ifdef SIGILL
-            case SIGILL:
-                handler = __signalTrapInterrupt;
-                break;
+	    case SIGILL:
+		handler = __signalTrapInterrupt;
+		break;
 #endif
 #ifdef SIGEMT
-            case SIGEMT:
-                handler = __signalTrapInterrupt;
-                break;
+	    case SIGEMT:
+		handler = __signalTrapInterrupt;
+		break;
 #endif
 #ifdef SIGIO
-            case SIGIO:
-                handler = __signalIoInterrupt;
-                break;
+	    case SIGIO:
+		handler = __signalIoInterrupt;
+		break;
 #endif
 
 #ifdef CHILD_SIGNAL
-            case CHILD_SIGNAL:
-                handler = __signalChildInterrupt;
-                break;
-#endif
-
-            default:
-                handler = __signalInterrupt;
-                break;
-        }
-
-        {
+	    case CHILD_SIGNAL:
+		handler = __signalChildInterrupt;
+		break;
+#endif
+
+	    default:
+		handler = __signalInterrupt;
+		break;
+	}
+
+	{
 #ifdef HAS_SIGACTION
-            struct sigaction act;
-
-            /*
-             * Do not add SA_RESTART here. A signal can cause a
-             * thread switch, another thread can do a garbage collect
-             * and restarted system calls may write into old
-             * (collected) addresses.
-             */
-
-            act.sa_flags = SA_SIGINFO; /* <- if you add more, remember dummys at the top */
-            sigemptyset(&act.sa_mask);
-            act.sa_handler = handler;
-            sigaction(sigNr, &act, 0);
+	    struct sigaction act;
+
+	    /*
+	     * Do not add SA_RESTART here. A signal can cause a
+	     * thread switch, another thread can do a garbage collect
+	     * and restarted system calls may write into old
+	     * (collected) addresses.
+	     */
+
+	    act.sa_flags = SA_SIGINFO; /* <- if you add more, remember dummys at the top */
+	    sigemptyset(&act.sa_mask);
+	    act.sa_handler = handler;
+	    sigaction(sigNr, &act, 0);
 #else
 # ifdef HAS_SIGVEC
-            struct sigvec vec;
-
-            vec.sv_flags = SV_INTERRUPT;
-            sigemptyset(&vec.sv_mask);
-            vec.sv_handler = handler;
-            sigvec(sigNr, &vec, NULL);
+	    struct sigvec vec;
+
+	    vec.sv_flags = SV_INTERRUPT;
+	    sigemptyset(&vec.sv_mask);
+	    vec.sv_handler = handler;
+	    sigvec(sigNr, &vec, NULL);
 # else
 #  ifdef WIN32
 #   ifdef SIGNALDEBUGWIN32
-            console_printf("signal %d can't change handler\n",sigNr);
+	    console_printf("signal %d can't change handler\n",sigNr);
 #   endif
 #  else
-            (void) signal(sigNr, handler);
+	    (void) signal(sigNr, handler);
 #  endif
 # endif
 #endif
-        }
-
-        /*
-         * maybe, we should Return the old enable-status
-         * as boolean here ...
-         */
-        RETURN (self);
+	}
+
+	/*
+	 * maybe, we should Return the old enable-status
+	 * as boolean here ...
+	 */
+	RETURN (self);
     }
 %}.
 
@@ -7289,8 +7202,8 @@
     extern void __win32SetTimer();
 
     if (__isSmallInteger(milliSeconds)) {
-        __win32SetTimer( __intVal(milliSeconds) );
-        RETURN (true);
+	__win32SetTimer( __intVal(milliSeconds) );
+	RETURN (true);
     }
 %}.
     ^ false
@@ -7310,8 +7223,8 @@
      The process terminates immediately and has no chance to perform any cleanup actions.
 
      WARNING: in order to avoid zombie processes (on unix),
-              you have to fetch the processes exitstatus with
-              OperatingSystem>>getStatusOfProcess:aProcessId."
+	      you have to fetch the processes exitstatus with
+	      OperatingSystem>>getStatusOfProcess:aProcessId."
 
     self terminateProcess:processId
 !
@@ -7321,8 +7234,8 @@
      The process(es) terminate immediately and has no chance to perform any cleanup actions.
 
      WARNING: in order to avoid zombie processes (on unix),
-              you have to fetch the processes exitstatus with
-              OperatingSystem>>getStatusOfProcess:aProcessId."
+	      you have to fetch the processes exitstatus with
+	      OperatingSystem>>getStatusOfProcess:aProcessId."
 
     self terminateProcessGroup:processGroupId
 !
@@ -7371,9 +7284,9 @@
      Do not confuse UNIX signals with Smalltalk-Signals.
 
      WARNING: in order to avoid zombie processes (on unix),
-              you may have to fetch the processes exitstatus with
-              OperatingSystem>>getStatusOfProcess:aProcessId
-              if the signal terminates that process."
+	      you may have to fetch the processes exitstatus with
+	      OperatingSystem>>getStatusOfProcess:aProcessId
+	      if the signal terminates that process."
 
     "/
     "/ either invalid argument (non-integers)
@@ -7389,9 +7302,9 @@
      Do not confuse UNIX signals with Smalltalk-Signals.
 
      WARNING: in order to avoid zombie processes (on unix),
-              you may have to fetch the processes exitstatus with
-              OperatingSystem>>getStatusOfProcess:aProcessId
-              if the signal terminates that process."
+	      you may have to fetch the processes exitstatus with
+	      OperatingSystem>>getStatusOfProcess:aProcessId
+	      if the signal terminates that process."
 
     "/
     "/ either invalid argument (non-integers)
@@ -7404,15 +7317,15 @@
     "terminate a process.
 
      ATTENTION WIN32:
-         Under unix, we have terminateProcess, which does a soft
-         terminate (giving the process a chance to cleanup) and
-         killProcess, which does a hard terminate.
-         Under WIN32, both (currently) use the TerminateProcess
-         function, which unconditionally causes a process to exit.
-         I.e. under WIN32, the process has no chance to perform cleanup.
-         Use it only in extreme circumstances. The state of
-         global data maintained by dynamic-link libraries (DLLs)
-         may be compromised if TerminateProcess is used.
+	 Under unix, we have terminateProcess, which does a soft
+	 terminate (giving the process a chance to cleanup) and
+	 killProcess, which does a hard terminate.
+	 Under WIN32, both (currently) use the TerminateProcess
+	 function, which unconditionally causes a process to exit.
+	 I.e. under WIN32, the process has no chance to perform cleanup.
+	 Use it only in extreme circumstances. The state of
+	 global data maintained by dynamic-link libraries (DLLs)
+	 may be compromised if TerminateProcess is used.
 
      TODO: send a WM_QUIT instead, to allow for proper shutdown."
 
@@ -7423,34 +7336,34 @@
     "terminate a process.
 
      ATTENTION WIN32:
-         Under unix, we have terminateProcess, which does a soft
-         terminate (giving the process a chance to cleanup) and
-         killProcess, which does a hard terminate.
-         Under WIN32, both (currently) use the TerminateProcess
-         function, which unconditionally causes a process to exit.
-         I.e. under WIN32, the process has no chance to perform cleanup.
-         Use it only in extreme circumstances. The state of
-         global data maintained by dynamic-link libraries (DLLs)
-         may be compromised if TerminateProcess is used.
+	 Under unix, we have terminateProcess, which does a soft
+	 terminate (giving the process a chance to cleanup) and
+	 killProcess, which does a hard terminate.
+	 Under WIN32, both (currently) use the TerminateProcess
+	 function, which unconditionally causes a process to exit.
+	 I.e. under WIN32, the process has no chance to perform cleanup.
+	 Use it only in extreme circumstances. The state of
+	 global data maintained by dynamic-link libraries (DLLs)
+	 may be compromised if TerminateProcess is used.
 
      TODO: send a WM_QUIT instead, to allow for proper shutdown."
 
 %{
     if (__isExternalAddressLike(processHandleOrPid) ) {
-        HANDLE hProcess = _HANDLEVal(processHandleOrPid);
-
-        if (hProcess != 0) {
-            TerminateProcess( hProcess, __intVal(exitCode) );
-        }
-        RETURN( true );
+	HANDLE hProcess = _HANDLEVal(processHandleOrPid);
+
+	if (hProcess != 0) {
+	    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 );
+	HANDLE hProcess = OpenProcess(PROCESS_TERMINATE, 0, __smallIntegerVal(processHandleOrPid));
+
+	if( hProcess != 0 ) {
+	    TerminateProcess( hProcess, __intVal(exitCode) );
+	    CloseHandle(hProcess);
+	}
+	RETURN( true );
     }
 %}.
     self primitiveFailed:#invalidParameter.
@@ -7464,15 +7377,15 @@
     "terminate a process group (that is all subprocesses of a process).
 
      ATTENTION WIN32:
-         Under unix, we have terminateProcess, which does a soft
-         terminate (giving the process a chance to cleanup) and
-         killProcess, which does a hard terminate.
-         Under WIN32, both (currently) use the TerminateProcess
-         function, which unconditionally causes a process to exit.
-         I.e. under WIN32, the process has no chance to perform cleanup.
-         Use it only in extreme circumstances. The state of
-         global data maintained by dynamic-link libraries (DLLs)
-         may be compromised if TerminateProcess is used.
+	 Under unix, we have terminateProcess, which does a soft
+	 terminate (giving the process a chance to cleanup) and
+	 killProcess, which does a hard terminate.
+	 Under WIN32, both (currently) use the TerminateProcess
+	 function, which unconditionally causes a process to exit.
+	 I.e. under WIN32, the process has no chance to perform cleanup.
+	 Use it only in extreme circumstances. The state of
+	 global data maintained by dynamic-link libraries (DLLs)
+	 may be compromised if TerminateProcess is used.
      TODO: send a WM_QUIT instead, to allow for proper shutdown."
 
     | pid list groupsToTerminate anyMore |
@@ -7481,9 +7394,9 @@
     list size == 0 ifTrue:[^ self ].
 
     processGroupHandleOrPid isInteger ifTrue:[
-        pid := processGroupHandleOrPid
+	pid := processGroupHandleOrPid
     ] ifFalse:[
-        pid := processGroupHandleOrPid pid.
+	pid := processGroupHandleOrPid pid.
     ].
     groupsToTerminate := Set with:pid.
     list := list asSet.
@@ -7491,21 +7404,21 @@
     "/ Transcript show:'terminate group '; showCR:pid.
     anyMore := true.
     [anyMore] whileTrue:[
-        anyMore := false.
-        list doWithExit:[:anOSProcess :exit |
-            |pid|
-
-            (groupsToTerminate includes:anOSProcess parentPid) ifTrue:[
-                pid := anOSProcess pid.
-                groupsToTerminate add:pid.
-                "/ Transcript show:'terminate '; showCR:pid.
-                self terminateProcess:( pid ).
-                list remove:anOSProcess.
-                anyMore := true.
-                "/ need to restart: we have removed an element inside the loop
-                exit value:nil
-            ].
-        ].
+	anyMore := false.
+	list doWithExit:[:anOSProcess :exit |
+	    |pid|
+
+	    (groupsToTerminate includes:anOSProcess parentPid) ifTrue:[
+		pid := anOSProcess pid.
+		groupsToTerminate add:pid.
+		"/ Transcript show:'terminate '; showCR:pid.
+		self terminateProcess:( pid ).
+		list remove:anOSProcess.
+		anyMore := true.
+		"/ need to restart: we have removed an element inside the loop
+		exit value:nil
+	    ].
+	].
     ].
 ! !
 
@@ -7532,8 +7445,8 @@
     sa.bInheritHandle = FALSE;
 
     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
@@ -7553,9 +7466,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
@@ -7567,15 +7480,15 @@
     "free pid resource"
 %{
     if (__isExternalAddressLike(pid) ) {
-        HANDLE __pid = _HANDLEVal(pid);
-
-        if (__pid != 0) {
+	HANDLE __pid = _HANDLEVal(pid);
+
+	if (__pid != 0) {
 #ifdef PROCESSDEBUGWIN32
-            console_printf("Close ProcessHandle %x\n", __pid);
-#endif
-            CloseHandle(__pid);
-            _SETHANDLEVal(pid, 0);
-        }
+	    console_printf("Close ProcessHandle %x\n", __pid);
+#endif
+	    CloseHandle(__pid);
+	    _SETHANDLEVal(pid, 0);
+	}
     }
 %}.
     ^ true.
@@ -7590,18 +7503,18 @@
     spaceForTargetHandle := ExternalLong unprotectedNew.
     hMe := self getCurrentProcess.
     rslt := self
-                primDuplicateHandle_hSourcProcessHandle:hMe
-                hSourceHandle:aHandle
-                hTargetProcesshandle:targetProcessHandle ? hMe
-                lpTargetHandle:spaceForTargetHandle
-                dwDesiredAccess:0
-                bInheritHandle:false
-                dwOptions:2 "DUPLICATE_SAME_ACCESS".
+		primDuplicateHandle_hSourcProcessHandle:hMe
+		hSourceHandle:aHandle
+		hTargetProcesshandle:targetProcessHandle ? hMe
+		lpTargetHandle:spaceForTargetHandle
+		dwDesiredAccess:0
+		bInheritHandle:false
+		dwOptions:2 "DUPLICATE_SAME_ACCESS".
 
     rslt ifFalse:[
-        spaceForTargetHandle free.
-        self primitiveFailed:self primGetLastError.
-        ^ nil
+	spaceForTargetHandle free.
+	self primitiveFailed:self primGetLastError.
+	^ nil
     ].
 
     addr := spaceForTargetHandle value.
@@ -7627,20 +7540,20 @@
     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);
-            f = __MKSTRING(pe32.szExeFile);
-            __SSEND1(st_perProc, @symbol(commandLine:), 0, f );
-            __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));
-        CloseHandle( hProcessSnap );
+	pe32.dwSize = sizeof(PROCESSENTRY32);
+	Process32First( hProcessSnap, & pe32 );
+
+	do {
+	    st_perProc = __SSEND0(@global(OSProcess), @symbol(new), 0);
+	    f = __MKSTRING(pe32.szExeFile);
+	    __SSEND1(st_perProc, @symbol(commandLine:), 0, f );
+	    __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));
+	CloseHandle( hProcessSnap );
     }
 
 #endif  /* TLHELP32_H_INCLUDE */
@@ -7661,8 +7574,8 @@
 
 getPrivateProfileString:appNameString key:keyNameString default:defaultString fileName:fileName
     ^ self
-        getProfileString:appNameString key:keyNameString default:defaultString
-        fileName:fileName private:true
+	getProfileString:appNameString key:keyNameString default:defaultString
+	fileName:fileName private:true
 
     "Modified: / 27-07-2006 / 11:57:03 / fm"
 !
@@ -7680,40 +7593,40 @@
     OBJ retVal;
 
     if (__isStringLike(appNameString)) {
-        __appNameString = __stringVal(appNameString);
+	__appNameString = __stringVal(appNameString);
     } else if (appNameString != nil)
-        goto primitiveFail;
+	goto primitiveFail;
 
     if (__isStringLike(keyNameString)) {
-        __keyNameString = __stringVal(keyNameString);
+	__keyNameString = __stringVal(keyNameString);
     } else if (keyNameString != nil)
-        goto primitiveFail;
+	goto primitiveFail;
 
     if (__isStringLike(defaultString)) {
-        __defaultString = __stringVal(defaultString);
+	__defaultString = __stringVal(defaultString);
     } else if (defaultString != nil)
-        goto primitiveFail;
+	goto primitiveFail;
 
     do {
-        nChars = GetProfileString(__appNameString, __keyNameString, __defaultString, usedBuffer, bufferSize);
-        if (nChars >= 0) {
-            if (nChars != bufferSize-1) {
-                retVal = __MKSTRING_L(usedBuffer, nChars);
-                if (usedBuffer != quickBuffer) free(usedBuffer);
-                RETURN (retVal);
-            }
-
-            {
-                /* use a bigger buffer */
-                char *newBuffer;
-                int newBufferSize = bufferSize * 2;
-
-                newBuffer = (char *)malloc( newBufferSize );
-                if (usedBuffer != quickBuffer) free(usedBuffer);
-                usedBuffer = newBuffer;
-                bufferSize = newBufferSize;
-            }
-        }
+	nChars = GetProfileString(__appNameString, __keyNameString, __defaultString, usedBuffer, bufferSize);
+	if (nChars >= 0) {
+	    if (nChars != bufferSize-1) {
+		retVal = __MKSTRING_L(usedBuffer, nChars);
+		if (usedBuffer != quickBuffer) free(usedBuffer);
+		RETURN (retVal);
+	    }
+
+	    {
+		/* use a bigger buffer */
+		char *newBuffer;
+		int newBufferSize = bufferSize * 2;
+
+		newBuffer = (char *)malloc( newBufferSize );
+		if (usedBuffer != quickBuffer) free(usedBuffer);
+		usedBuffer = newBuffer;
+		bufferSize = newBufferSize;
+	    }
+	}
 
     } while (nChars > 0);
     RETURN (nil);
@@ -7738,49 +7651,49 @@
     OBJ retVal;
 
     if (__isStringLike(appNameString)) {
-        __appNameString = __stringVal(appNameString);
+	__appNameString = __stringVal(appNameString);
     } else if (appNameString != nil)
-        goto primitiveFail;
+	goto primitiveFail;
 
     if (__isStringLike(keyNameString)) {
-        __keyNameString = __stringVal(keyNameString);
+	__keyNameString = __stringVal(keyNameString);
     } else if (keyNameString != nil)
-        goto primitiveFail;
+	goto primitiveFail;
 
     if (__isStringLike(defaultString)) {
-        __defaultString = __stringVal(defaultString);
+	__defaultString = __stringVal(defaultString);
     } else if (defaultString != nil)
-        goto primitiveFail;
+	goto primitiveFail;
 
     if (private == true) {
-        if (! __isStringLike(fileName)) goto primitiveFail;
-        __fileName = __stringVal(fileName);
+	if (! __isStringLike(fileName)) goto primitiveFail;
+	__fileName = __stringVal(fileName);
     }
 
     do {
-        if (private == true) {
-            nChars = GetPrivateProfileString(__appNameString, __keyNameString, __defaultString, usedBuffer, bufferSize, __fileName);
-        } else {
-            nChars = GetProfileString(__appNameString, __keyNameString, __defaultString, usedBuffer, bufferSize);
-        }
-        if (nChars >= 0) {
-            if (nChars != bufferSize-1) {
-                retVal = __MKSTRING_L(usedBuffer, nChars);
-                if (usedBuffer != quickBuffer) free(usedBuffer);
-                RETURN (retVal);
-            }
-
-            {
-                /* use a bigger buffer */
-                char *newBuffer;
-                int newBufferSize = bufferSize * 2;
-
-                newBuffer = (char *)malloc( newBufferSize );
-                if (usedBuffer != quickBuffer) free(usedBuffer);
-                usedBuffer = newBuffer;
-                bufferSize = newBufferSize;
-            }
-        }
+	if (private == true) {
+	    nChars = GetPrivateProfileString(__appNameString, __keyNameString, __defaultString, usedBuffer, bufferSize, __fileName);
+	} else {
+	    nChars = GetProfileString(__appNameString, __keyNameString, __defaultString, usedBuffer, bufferSize);
+	}
+	if (nChars >= 0) {
+	    if (nChars != bufferSize-1) {
+		retVal = __MKSTRING_L(usedBuffer, nChars);
+		if (usedBuffer != quickBuffer) free(usedBuffer);
+		RETURN (retVal);
+	    }
+
+	    {
+		/* use a bigger buffer */
+		char *newBuffer;
+		int newBufferSize = bufferSize * 2;
+
+		newBuffer = (char *)malloc( newBufferSize );
+		if (usedBuffer != quickBuffer) free(usedBuffer);
+		usedBuffer = newBuffer;
+		bufferSize = newBufferSize;
+	    }
+	}
 
     } while (nChars > 0);
     RETURN (nil);
@@ -7810,7 +7723,7 @@
 
     newHandle := self duplicateHandle:anExternalAddress to:nil.
     newHandle isNil ifTrue:[
-        ^ false.
+	^ false.
     ].
 "/    self closeHandle:newHandle.
     ^ true.
@@ -7827,7 +7740,7 @@
 
     "
      self
-        playSound:'C:\Dokumente und Einstellungen\cg\work\exept\expecco\resources\sounds\start.wav'
+	playSound:'C:\Dokumente und Einstellungen\cg\work\exept\expecco\resources\sounds\start.wav'
     "
 
     "Created: / 06-11-2007 / 00:46:57 / cg"
@@ -7845,8 +7758,8 @@
 
     "
      self
-        playSound:'C:\Dokumente und Einstellungen\cg\work\exept\expecco\resources\sounds\start.wav'
-        mode:1
+	playSound:'C:\Dokumente und Einstellungen\cg\work\exept\expecco\resources\sounds\start.wav'
+	mode:1
     "
 
     "Modified: / 06-11-2007 / 00:46:27 / cg"
@@ -7883,7 +7796,7 @@
     "/ <apicall: dword "GetLastError" () module: "kernel32.dll" >
 
     "
-        self primGetLastError
+	self primGetLastError
     "
 !
 
@@ -7892,8 +7805,8 @@
 
 %{  /* NOCONTEXT */
     if (__isSmallInteger(i)) {
-        SetLastError(__intVal(i));
-        RETURN(self);
+	SetLastError(__intVal(i));
+	RETURN(self);
     }
 %}.
    "/ <apicall: void "SetLastError" (dword) module: "kernel32.dll" >
@@ -7910,10 +7823,10 @@
      && __isString(keyName)
      && __isString(profString)
      && __isString(fnString)) {
-        BOOL ret;
-
-        ret = WritePrivateProfileStringA(__stringVal(appName), __stringVal(keyName), __stringVal(profString), __stringVal(fnString));
-        RETURN( ret == 0 ? false : true);
+	BOOL ret;
+
+	ret = WritePrivateProfileStringA(__stringVal(appName), __stringVal(keyName), __stringVal(profString), __stringVal(fnString));
+	RETURN( ret == 0 ? false : true);
     }
 %}.
 
@@ -7957,8 +7870,8 @@
     "/    lastErrorCode == 5 "ERROR_ACCESS_DENIED" ifTrue:[Transcript showCR: 'Mutex not accesible (GetLastError = ERROR_ACCESS_DENIED)'.].
     "/    lastErrorCode == 183 "ERROR_ALREADY_EXISTS" ifTrue:[Transcript showCR: 'Mutex already exists (GetLastError = ERROR_ALREADY_EXISTS)'.].
     (handle isNil or:[handle address ~~ 0]) ifFalse:[
-        Transcript showCR: 'CreateMutexNamed: "', name printString, '" failed'.
-        handle := nil.
+	Transcript showCR: 'CreateMutexNamed: "', name printString, '" failed'.
+	handle := nil.
     ].
     ^ Array with: handle with: lastErrorCode
 
@@ -7978,8 +7891,8 @@
     lastErrorCode := handleAndLastErrorCode second.
     "/  self assert: lastErrorCode == 0.
     ^ handle isNil
-        or:[lastErrorCode == 183 "ERROR_ALREADY_EXISTS"
-            or:[ lastErrorCode == 5 "ERROR_ACCESS_DENIED"]]
+	or:[lastErrorCode == 183 "ERROR_ALREADY_EXISTS"
+	    or:[ lastErrorCode == 5 "ERROR_ACCESS_DENIED"]]
 
     "Modified: / 03-08-2010 / 16:59:41 / cg"
 !
@@ -7996,8 +7909,8 @@
     "/    lastErrorCode = 2 ifTrue:[Transcript showCR: 'Mutex does not exist (GetLastError = ERROR_FILE_NOT_FOUND)'.].
     "/    lastErrorCode = 5 ifTrue:[Transcript showCR: 'Mutex not accessable (GetLastError = ERROR_ACCESS_DENIED)'.].
     (handle isNil or:[handle address ~~ 0]) ifFalse:[
-        Transcript showCR: 'OpenMutexNamed: "', name printString, '" failed'.
-        ^ nil.
+	Transcript showCR: 'OpenMutexNamed: "', name printString, '" failed'.
+	^ nil.
     ].
     ^ handle
 
@@ -8019,23 +7932,23 @@
 %{
     if (__isString(lpName)
      && ((bInitialOwner == true) || (bInitialOwner == false))) {
-        void *c_descr = NULL;
-        char *c_name;
-        BOOL c_initialOwner = (bInitialOwner == true);
-        HANDLE c_handle;
-
-        c_name = __stringVal(lpName);
-
-        if (lpSecurityDescriptor != nil) {
-            if (__isExternalAddressLike(lpSecurityDescriptor)
-             || __isExternalBytesLike(lpSecurityDescriptor) ) {
-                c_descr = __externalAddressVal(lpSecurityDescriptor);
-            } else
-                goto badArg;
-        }
-        c_handle = CreateMutexA(c_descr, c_initialOwner, c_name);
-        __externalAddressVal(handle) = c_handle;
-        RETURN(handle);
+	void *c_descr = NULL;
+	char *c_name;
+	BOOL c_initialOwner = (bInitialOwner == true);
+	HANDLE c_handle;
+
+	c_name = __stringVal(lpName);
+
+	if (lpSecurityDescriptor != nil) {
+	    if (__isExternalAddressLike(lpSecurityDescriptor)
+	     || __isExternalBytesLike(lpSecurityDescriptor) ) {
+		c_descr = __externalAddressVal(lpSecurityDescriptor);
+	    } else
+		goto badArg;
+	}
+	c_handle = CreateMutexA(c_descr, c_initialOwner, c_name);
+	__externalAddressVal(handle) = c_handle;
+	RETURN(handle);
     }
     badArg: ;
 %}.
@@ -8056,22 +7969,22 @@
 %{
     if (__isString(lpName)
      && ((bInitialOwner == true) || (bInitialOwner == false))) {
-        DWORD c_dwDesiredAccess = 0;
-        char *c_name;
-        BOOL c_initialOwner = (bInitialOwner == true);
-        HANDLE c_handle;
-
-        c_name = __stringVal(lpName);
-
-        if (dwDesiredAccess != nil) {
-            if (! __isSmallInteger(dwDesiredAccess)) {
-                goto badArg;
-            }
-            c_dwDesiredAccess = __intVal(dwDesiredAccess);
-        }
-        c_handle = OpenMutexA(c_dwDesiredAccess, c_initialOwner, c_name);
-        __externalAddressVal(handle) = c_handle;
-        RETURN(handle);
+	DWORD c_dwDesiredAccess = 0;
+	char *c_name;
+	BOOL c_initialOwner = (bInitialOwner == true);
+	HANDLE c_handle;
+
+	c_name = __stringVal(lpName);
+
+	if (dwDesiredAccess != nil) {
+	    if (! __isSmallInteger(dwDesiredAccess)) {
+		goto badArg;
+	    }
+	    c_dwDesiredAccess = __intVal(dwDesiredAccess);
+	}
+	c_handle = OpenMutexA(c_dwDesiredAccess, c_initialOwner, c_name);
+	__externalAddressVal(handle) = c_handle;
+	RETURN(handle);
     }
     badArg: ;
 %}.
@@ -8087,11 +8000,11 @@
 %{
     if (__isExternalAddressLike(hMutex)
      || __isExternalBytesLike(hMutex) ) {
-        HANDLE _handle = _HANDLEVal(hMutex);
-        BOOL _ret;
-
-        _ret = ReleaseMutex(_handle);
-        RETURN(_ret == 0 ? false : true);
+	HANDLE _handle = _HANDLEVal(hMutex);
+	BOOL _ret;
+
+	_ret = ReleaseMutex(_handle);
+	RETURN(_ret == 0 ? false : true);
     }
 %}.
     "/ <apicall: bool "ReleaseMutex" (handle) module: "kernel32.dll" >
@@ -8107,15 +8020,15 @@
 %{
     if (__isExternalAddressLike(handle)
      || __isExternalBytesLike(handle) ) {
-        HANDLE _handle = _HANDLEVal(handle);
-
-        if (__isSmallInteger(dwMilliseconds)) {
-            DWORD _millis = __intVal(dwMilliseconds);
-            DWORD _ret;
-
-            _ret = ReleaseMutex(_handle);
-            RETURN( __mkSmallInteger(_ret));
-        }
+	HANDLE _handle = _HANDLEVal(handle);
+
+	if (__isSmallInteger(dwMilliseconds)) {
+	    DWORD _millis = __intVal(dwMilliseconds);
+	    DWORD _ret;
+
+	    _ret = ReleaseMutex(_handle);
+	    RETURN( __mkSmallInteger(_ret));
+	}
     }
 %}.
     "/ <apicall: dword "WaitForSingleObject" (handle dword) module: "kernel32.dll" >
@@ -8130,8 +8043,8 @@
     | released|
 
     hMutex isNil ifTrue:[
-        Transcript showCR: 'hMutex is nil - cannot release'.
-        ^ false
+	Transcript showCR: 'hMutex is nil - cannot release'.
+	^ false
     ].
     released := self primReleaseMutex: hMutex.
     released ifFalse:[Transcript showCR: 'Release Mutex failed'.].
@@ -8147,8 +8060,8 @@
 
     hMutex := self openMutexNamed: name.
     hMutex isNil ifTrue:[
-        Transcript showCR: 'Cannot release Mutex named: "', name printString,'"'.
-        ^ false
+	Transcript showCR: 'Cannot release Mutex named: "', name printString,'"'.
+	^ false
     ].
     ^ self releaseMutex: hMutex.
 
@@ -8181,39 +8094,39 @@
 %{
     if (__isString(aDirectoryPathName)
      && __isSmallInteger(changeFlags)) {
-        char *__dirName = __stringVal(aDirectoryPathName);
-        INT __flags = __intVal(changeFlags);
-        HANDLE __changeHandle;
-
-        __changeHandle = FindFirstChangeNotification(__dirName, FALSE, __flags);
-        if (__changeHandle == INVALID_HANDLE_VALUE) {
-            console_printf("failed to create handle\n");
-        } else {
-            __externalAddressVal(handle) = __changeHandle;
-            RETURN (handle);
-        }
+	char *__dirName = __stringVal(aDirectoryPathName);
+	INT __flags = __intVal(changeFlags);
+	HANDLE __changeHandle;
+
+	__changeHandle = FindFirstChangeNotification(__dirName, FALSE, __flags);
+	if (__changeHandle == INVALID_HANDLE_VALUE) {
+	    console_printf("failed to create handle\n");
+	} else {
+	    __externalAddressVal(handle) = __changeHandle;
+	    RETURN (handle);
+	}
     }
 %}.
     self primitiveFailed
 
     "
-        |h|
-
-        [
-            h := OperatingSystem createChangeNotificationHandleFor:'.'
-                flags:(FILE_NOTIFY_CHANGE_FILE_NAME  |
-                       FILE_NOTIFY_CHANGE_DIR_NAME |
-                       FILE_NOTIFY_CHANGE_ATTRIBUTES |
-                       FILE_NOTIFY_CHANGE_SIZE |
-                       FILE_NOTIFY_CHANGE_LAST_WRITE).
-            Transcript showCR:'waiting...'.
-            OperatingSystem waitForSingleObject:h withTimeout:1000.
-            Transcript showCR:'got a change...'.
-            h close.
-        ] fork.
-        Delay waitForSeconds:0.25.
-        Transcript showCR:'changing...'.
-        './bla' asFilename contents:'hello'.
+	|h|
+
+	[
+	    h := OperatingSystem createChangeNotificationHandleFor:'.'
+		flags:(FILE_NOTIFY_CHANGE_FILE_NAME  |
+		       FILE_NOTIFY_CHANGE_DIR_NAME |
+		       FILE_NOTIFY_CHANGE_ATTRIBUTES |
+		       FILE_NOTIFY_CHANGE_SIZE |
+		       FILE_NOTIFY_CHANGE_LAST_WRITE).
+	    Transcript showCR:'waiting...'.
+	    OperatingSystem waitForSingleObject:h withTimeout:1000.
+	    Transcript showCR:'got a change...'.
+	    h close.
+	] fork.
+	Delay waitForSeconds:0.25.
+	Transcript showCR:'changing...'.
+	'./bla' asFilename contents:'hello'.
 
     "
 ! !
@@ -8224,7 +8137,7 @@
     "return a collection of extensions for executable program files.
      Only req'd for msdos like systems ..."
 
-    ^ #('com' 'exe' 'bat')
+    ^ #('com' 'exe' 'bat' 'cmd')
 
     "Created: / 02-05-1997 / 11:42:29 / cg"
     "Modified: / 23-08-2011 / 21:14:45 / jv"
@@ -8237,70 +8150,70 @@
 
     count := aString size + 128.
     [
-        aString isWideString ifTrue:[
-            resultString := Unicode16String new:count.
-            resultCount := self primExpandEnvironmentStringsW:aString into:resultString size:count.
-        ] ifFalse:[
-            resultString := String new:count.
-            resultCount := self primExpandEnvironmentStringsA:aString into:resultString size:count.
-        ].
-        resultCount <= count ifTrue:[
-            true
-        ] ifFalse:[
-            "resultString was too small. resultCount is the required buffer size"
-            count := resultCount.
-            false
-        ].
+	aString isWideString ifTrue:[
+	    resultString := Unicode16String new:count.
+	    resultCount := self primExpandEnvironmentStringsW:aString into:resultString size:count.
+	] ifFalse:[
+	    resultString := String new:count.
+	    resultCount := self primExpandEnvironmentStringsA:aString into:resultString size:count.
+	].
+	resultCount <= count ifTrue:[
+	    true
+	] ifFalse:[
+	    "resultString was too small. resultCount is the required buffer size"
+	    count := resultCount.
+	    false
+	].
     ] whileFalse.
     ^ resultString copyTo:resultCount-1.
 
 
     "
-        self expandEnvironmentStrings:'%ProgramFiles%\test\x'
-        self expandEnvironmentStrings:'%ProgramFiles%\test\x' asUnicode16String
+	self expandEnvironmentStrings:'%ProgramFiles%\test\x'
+	self expandEnvironmentStrings:'%ProgramFiles%\test\x' asUnicode16String
     "
 !
 
 getDomainName
     "return the DNS domain this host is in.
      Notice:
-        not all systems support this; on some, 'unknown' is returned."
+	not all systems support this; on some, 'unknown' is returned."
 
     |domainName idx hostName k|
 
     DomainName notNil ifTrue:[
-        ^ DomainName
+	^ DomainName
     ].
 
     "/ sometimes, we can extract the domainName from the hostName ...
     hostName := self getHostName.
     hostName notEmptyOrNil ifTrue:[
-        idx := hostName indexOf:$..
-        idx ~~ 0 ifTrue:[
-            domainName := hostName copyFrom:idx+1.
-        ]
+	idx := hostName indexOf:$..
+	idx ~~ 0 ifTrue:[
+	    domainName := hostName copyFrom:idx+1.
+	]
     ].
 
     domainName isNil ifTrue:[
-        domainName := self getEnvironment:'DOMAIN'.
-        domainName isNil ifTrue:[
-            domainName := self getEnvironment:'DOMAINNAME'.
-        ].
-
-        domainName isNil ifTrue:[
-            "/ ok, search the registry ...
-            "/ under NT and later, it is found there ...
-            k := RegistryEntry key:'HKEY_LOCAL_MACHINE\SYSTEM\CurrentControlSet\Services\Tcpip\Parameters'.
-            k notNil ifTrue:[
-                domainName := k valueNamed:'Domain'.
-                k close.
-            ].
-        ].
-
-        domainName isNil ifTrue:[
-            ^ 'unknown'.
-        ].
-        DomainName := domainName.     "cache only, if it is fixed"
+	domainName := self getEnvironment:'DOMAIN'.
+	domainName isNil ifTrue:[
+	    domainName := self getEnvironment:'DOMAINNAME'.
+	].
+
+	domainName isNil ifTrue:[
+	    "/ ok, search the registry ...
+	    "/ under NT and later, it is found there ...
+	    k := RegistryEntry key:'HKEY_LOCAL_MACHINE\SYSTEM\CurrentControlSet\Services\Tcpip\Parameters'.
+	    k notNil ifTrue:[
+		domainName := k valueNamed:'Domain'.
+		k close.
+	    ].
+	].
+
+	domainName isNil ifTrue:[
+	    ^ 'unknown'.
+	].
+	DomainName := domainName.     "cache only, if it is fixed"
     ].
     ^ domainName
 
@@ -8325,35 +8238,35 @@
     int i, l;
 
     if (__isStringLike(aStringOrSymbol)) {
-        l = __stringSize(aStringOrSymbol);
-        if (l > ENV_BUFSIZE-1)
-            goto badArgument;
-        for (i=0; i<l; i++) {
-            _varName[i] = __stringVal(aStringOrSymbol)[i];
-        }
+	l = __stringSize(aStringOrSymbol);
+	if (l > ENV_BUFSIZE-1)
+	    goto badArgument;
+	for (i=0; i<l; i++) {
+	    _varName[i] = __stringVal(aStringOrSymbol)[i];
+	}
     } else if (__isUnicode16String(aStringOrSymbol)) {
-        l = __unicode16StringSize(aStringOrSymbol);
-        if (l > ENV_BUFSIZE-1)
-            goto badArgument;
-        for (i=0; i<l; i++) {
-            _varName[i] = __unicode16StringVal(aStringOrSymbol)[i];
-        }
+	l = __unicode16StringSize(aStringOrSymbol);
+	if (l > ENV_BUFSIZE-1)
+	    goto badArgument;
+	for (i=0; i<l; i++) {
+	    _varName[i] = __unicode16StringVal(aStringOrSymbol)[i];
+	}
     } else {
-        goto badArgument;
+	goto badArgument;
     }
     _varName[l] = 0;
 
     nNeeded = GetEnvironmentVariableW(_varName, buff, ENV_BUFSIZE);
     if (nNeeded > sizeof(buff)) {
-        WCHAR *buff2;
-
-        buff2 = (char *)malloc(nNeeded * sizeof(WCHAR));
-        GetEnvironmentVariableW(_varName, buff2, nNeeded);
-        ret = __mkStringOrU16String_maxlen(buff2, nNeeded);
-        free(buff2);
+	WCHAR *buff2;
+
+	buff2 = (char *)malloc(nNeeded * sizeof(WCHAR));
+	GetEnvironmentVariableW(_varName, buff2, nNeeded);
+	ret = __mkStringOrU16String_maxlen(buff2, nNeeded);
+	free(buff2);
     } else if (nNeeded > 0) {
-        ret = __mkStringOrU16String_maxlen(buff, nNeeded);
-        // console_printf("getenv() -> %"_lx_"\n", (INT)ret);
+	ret = __mkStringOrU16String_maxlen(buff, nNeeded);
+	// console_printf("getenv() -> %"_lx_"\n", (INT)ret);
     }
     RETURN (ret);
 
@@ -8386,11 +8299,11 @@
     // Note: GetComputerNameExA can fail in certain locales!
 #if defined(__MINGW32__)
     if (GetComputerNameA(bufferA, &buffSize) == TRUE) {
-        RETURN(__MKSTRING_L(bufferA, buffSize));
+	RETURN(__MKSTRING_L(bufferA, buffSize));
     }
 #else
     if (GetComputerNameExW(ComputerNameDnsFullyQualified, buffer, &buffSize) == TRUE) {
-        RETURN(__mkStringOrU16String_maxlen(buffer, buffSize));
+	RETURN(__mkStringOrU16String_maxlen(buffer, buffSize));
     }
 #endif
 %}.
@@ -8408,14 +8321,14 @@
 
     lang := self getEnvironment:'LANG'.
     (lang isNil or:[lang = 'default']) ifTrue:[
-        "/ ok, search the registry ...
-        "/ under XP, it is found there ...
-        lang := RegistryEntry
-                    stringValueFor:'sLanguage'
-                    atKey:'HKEY_CURRENT_USER\Control Panel\International'.
-        lang notNil ifTrue:[
-            lang := self mapLanguage:lang.
-        ].
+	"/ ok, search the registry ...
+	"/ under XP, it is found there ...
+	lang := RegistryEntry
+		    stringValueFor:'sLanguage'
+		    atKey:'HKEY_CURRENT_USER\Control Panel\International'.
+	lang notNil ifTrue:[
+	    lang := self mapLanguage:lang.
+	].
     ].
     ^ lang
 
@@ -8429,28 +8342,28 @@
     "return a dictionary filled with values from the locale information;
      Not all fields may be present, depending on the OS's setup and capabilities.
      Possible fields are:
-        decimalPoint                    <String>
-        thousandsSep                    <String>
-        internationalCurrencySymbol     <String>
-        currencySymbol                  <String>
-        monetaryDecimalPoint            <String>
-        monetaryThousandsSeparator      <String>
-        positiveSign                    <String>
-        negativeSign                    <String>
-        internationalFractionalDigits   <Integer>
-        fractionalDigits                <Integer>
-        positiveSignPrecedesCurrencySymbol      <Boolean>
-        negativeSignPrecedesCurrencySymbol      <Boolean>
-        positiveSignSeparatedBySpaceFromCurrencySymbol  <Boolean>
-        negativeSignSeparatedBySpaceFromCurrencySymbol  <Boolean>
-        positiveSignPosition                            <Symbol>
-                                                        one of: #parenthesesAround,
-                                                                #signPrecedes,
-                                                                #signSuceeds,
-                                                                #signPrecedesCurrencySymbol,
-                                                                #signSuceedsCurrencySymbol
-
-        negativeSignPosition                            <like above>
+	decimalPoint                    <String>
+	thousandsSep                    <String>
+	internationalCurrencySymbol     <String>
+	currencySymbol                  <String>
+	monetaryDecimalPoint            <String>
+	monetaryThousandsSeparator      <String>
+	positiveSign                    <String>
+	negativeSign                    <String>
+	internationalFractionalDigits   <Integer>
+	fractionalDigits                <Integer>
+	positiveSignPrecedesCurrencySymbol      <Boolean>
+	negativeSignPrecedesCurrencySymbol      <Boolean>
+	positiveSignSeparatedBySpaceFromCurrencySymbol  <Boolean>
+	negativeSignSeparatedBySpaceFromCurrencySymbol  <Boolean>
+	positiveSignPosition                            <Symbol>
+							one of: #parenthesesAround,
+								#signPrecedes,
+								#signSuceeds,
+								#signPrecedesCurrencySymbol,
+								#signSuceedsCurrencySymbol
+
+	negativeSignPosition                            <like above>
 
      it is up to the application to deal with undefined values.
 
@@ -8461,9 +8374,9 @@
     |info val|
 
     LocaleInfo notNil ifTrue:[
-        "/ return the internal info; useful on systems which do not
-        "/ support this.
-        ^ LocaleInfo
+	"/ return the internal info; useful on systems which do not
+	"/ support this.
+	^ LocaleInfo
     ].
 
     info := IdentityDictionary new.
@@ -8484,31 +8397,31 @@
     int   csNegSepBySpace;      /* money: 1 if currency symbol should be separated by a space from a negative value; 0 if no space */
     int   csPosSignPosition;    /* money: 0: ()'s around the value & currency symbol */
     int   csNegSignPosition;    /*        1: sign precedes the value & currency symbol */
-                                /*        2: sign succeeds the value & currency symbol */
-                                /*        3: sign immediately precedes the currency symbol */
-                                /*        4: sign immediately suceeds the currency symbol */
+				/*        2: sign succeeds the value & currency symbol */
+				/*        3: sign immediately precedes the currency symbol */
+				/*        4: sign immediately suceeds the currency symbol */
 
 #if defined(HAS_LOCALECONV)
     struct lconv *conf;
 
     conf = localeconv();
     if (conf) {
-        decimalPoint = conf->decimal_point;
-        thousandsSep = conf->thousands_sep;
-        intCurrencySymbol = conf->int_curr_symbol;
-        currencySymbol = conf->currency_symbol;
-        monDecimalPoint = conf->mon_decimal_point;
-        monThousandsSep = conf->mon_thousands_sep;
-        positiveSign = conf->positive_sign;
-        negativeSign = conf->negative_sign;
-        intFractDigits = conf->int_frac_digits;
-        fractDigits = conf->frac_digits;
-        csPosPrecedes = conf->p_cs_precedes;
-        csNegPrecedes = conf->n_cs_precedes;
-        csPosSepBySpace = conf->p_sep_by_space;
-        csNegSepBySpace = conf->n_sep_by_space;
-        csPosSignPosition = conf->p_sign_posn;
-        csNegSignPosition = conf->n_sign_posn;
+	decimalPoint = conf->decimal_point;
+	thousandsSep = conf->thousands_sep;
+	intCurrencySymbol = conf->int_curr_symbol;
+	currencySymbol = conf->currency_symbol;
+	monDecimalPoint = conf->mon_decimal_point;
+	monThousandsSep = conf->mon_thousands_sep;
+	positiveSign = conf->positive_sign;
+	negativeSign = conf->negative_sign;
+	intFractDigits = conf->int_frac_digits;
+	fractDigits = conf->frac_digits;
+	csPosPrecedes = conf->p_cs_precedes;
+	csNegPrecedes = conf->n_cs_precedes;
+	csPosSepBySpace = conf->p_sep_by_space;
+	csNegSepBySpace = conf->n_sep_by_space;
+	csPosSignPosition = conf->p_sign_posn;
+	csNegSignPosition = conf->n_sign_posn;
     }
 #else
     decimalPoint = (char *)0;
@@ -8529,129 +8442,129 @@
     csNegSignPosition = -1;
 #endif
     if (decimalPoint) {
-        val = __MKSTRING(decimalPoint);
-        __AT_PUT_(info, @symbol(decimalPoint), val);
+	val = __MKSTRING(decimalPoint);
+	__AT_PUT_(info, @symbol(decimalPoint), val);
     }
     if (thousandsSep) {
-        val = __MKSTRING(thousandsSep);
-        __AT_PUT_(info, @symbol(thousandsSeparator), val);
+	val = __MKSTRING(thousandsSep);
+	__AT_PUT_(info, @symbol(thousandsSeparator), val);
     }
     if (intCurrencySymbol) {
-        val = __MKSTRING(intCurrencySymbol);
-        __AT_PUT_(info, @symbol(internationCurrencySymbol), val);
+	val = __MKSTRING(intCurrencySymbol);
+	__AT_PUT_(info, @symbol(internationCurrencySymbol), val);
     }
     if (currencySymbol) {
-        val = __MKSTRING(currencySymbol);
-        __AT_PUT_(info, @symbol(currencySymbol), val);
+	val = __MKSTRING(currencySymbol);
+	__AT_PUT_(info, @symbol(currencySymbol), val);
     }
     if (monDecimalPoint) {
-        val = __MKSTRING(monDecimalPoint);
-        __AT_PUT_(info, @symbol(monetaryDecimalPoint), val);
+	val = __MKSTRING(monDecimalPoint);
+	__AT_PUT_(info, @symbol(monetaryDecimalPoint), val);
     }
     if (monThousandsSep) {
-        val = __MKSTRING(monThousandsSep);
-        __AT_PUT_(info, @symbol(monetaryThousandsSeparator), val);
+	val = __MKSTRING(monThousandsSep);
+	__AT_PUT_(info, @symbol(monetaryThousandsSeparator), val);
     }
     if (positiveSign) {
-        val = __MKSTRING(positiveSign);
-        __AT_PUT_(info, @symbol(positiveSign), val);
+	val = __MKSTRING(positiveSign);
+	__AT_PUT_(info, @symbol(positiveSign), val);
     }
     if (negativeSign) {
-        val = __MKSTRING(negativeSign);
-        __AT_PUT_(info, @symbol(negativeSign), val);
+	val = __MKSTRING(negativeSign);
+	__AT_PUT_(info, @symbol(negativeSign), val);
     }
     if (intFractDigits >= 0) {
-        __AT_PUT_(info, @symbol(internationalFractionalDigits),  __mkSmallInteger(intFractDigits));
+	__AT_PUT_(info, @symbol(internationalFractionalDigits),  __mkSmallInteger(intFractDigits));
     }
     if (fractDigits >= 0) {
-        __AT_PUT_(info, @symbol(fractionalDigits),  __mkSmallInteger(fractDigits));
+	__AT_PUT_(info, @symbol(fractionalDigits),  __mkSmallInteger(fractDigits));
     }
     if (csPosPrecedes >= 0) {
-        if (csPosPrecedes == 0) {
-            val = false;
-        } else {
-            val = true;
-        }
-        __AT_PUT_(info, @symbol(positiveSignPrecedesCurrencySymbol), val );
+	if (csPosPrecedes == 0) {
+	    val = false;
+	} else {
+	    val = true;
+	}
+	__AT_PUT_(info, @symbol(positiveSignPrecedesCurrencySymbol), val );
     }
     if (csNegPrecedes >= 0) {
-        if (csNegPrecedes == 0) {
-            val = false;
-        } else {
-            val = true;
-        }
-        __AT_PUT_(info, @symbol(negativeSignPrecedesCurrencySymbol), val );
+	if (csNegPrecedes == 0) {
+	    val = false;
+	} else {
+	    val = true;
+	}
+	__AT_PUT_(info, @symbol(negativeSignPrecedesCurrencySymbol), val );
     }
     if (csPosSepBySpace >= 0) {
-        if (csPosSepBySpace == 0) {
-            val = false;
-        } else {
-            val = true;
-        }
-        __AT_PUT_(info, @symbol(positiveSignSeparatedBySpaceFromCurrencySymbol), val);
+	if (csPosSepBySpace == 0) {
+	    val = false;
+	} else {
+	    val = true;
+	}
+	__AT_PUT_(info, @symbol(positiveSignSeparatedBySpaceFromCurrencySymbol), val);
     }
     if (csNegSepBySpace >= 0) {
-        if (csNegSepBySpace == 0) {
-            val = false;
-        } else {
-            val = true;
-        }
-        __AT_PUT_(info, @symbol(negativeSignSeparatedBySpaceFromCurrencySymbol), val);
+	if (csNegSepBySpace == 0) {
+	    val = false;
+	} else {
+	    val = true;
+	}
+	__AT_PUT_(info, @symbol(negativeSignSeparatedBySpaceFromCurrencySymbol), val);
     }
     switch (csPosSignPosition) {
-        case 0:
-            val = @symbol(parenthesesAround);
-            break;
-
-        case 1:
-            val = @symbol(signPrecedes);
-            break;
-
-        case 2:
-            val = @symbol(signSuceeds);
-            break;
-
-        case 3:
-            val = @symbol(signPrecedesCurrencySymbol);
-            break;
-
-        case 4:
-            val = @symbol(signSuceedsCurrencySymbol);
-            break;
-
-        default:
-            val = nil;
+	case 0:
+	    val = @symbol(parenthesesAround);
+	    break;
+
+	case 1:
+	    val = @symbol(signPrecedes);
+	    break;
+
+	case 2:
+	    val = @symbol(signSuceeds);
+	    break;
+
+	case 3:
+	    val = @symbol(signPrecedesCurrencySymbol);
+	    break;
+
+	case 4:
+	    val = @symbol(signSuceedsCurrencySymbol);
+	    break;
+
+	default:
+	    val = nil;
     }
     if (val != nil) {
-        __AT_PUT_(info, @symbol(positiveSignPosition), val);
+	__AT_PUT_(info, @symbol(positiveSignPosition), val);
     }
 
     switch (csNegSignPosition) {
-        case 0:
-            val = @symbol(parenthesesAround);
-            break;
-
-        case 1:
-            val = @symbol(signPrecedes);
-            break;
-
-        case 2:
-            val = @symbol(signSuceeds);
-            break;
-
-        case 3:
-            val = @symbol(signPrecedesCurrencySymbol);
-            break;
-
-        case 4:
-            val = @symbol(signSuceedsCurrencySymbol);
-            break;
-
-        default:
-            val = nil;
+	case 0:
+	    val = @symbol(parenthesesAround);
+	    break;
+
+	case 1:
+	    val = @symbol(signPrecedes);
+	    break;
+
+	case 2:
+	    val = @symbol(signSuceeds);
+	    break;
+
+	case 3:
+	    val = @symbol(signPrecedesCurrencySymbol);
+	    break;
+
+	case 4:
+	    val = @symbol(signSuceedsCurrencySymbol);
+	    break;
+
+	default:
+	    val = nil;
     }
     if (val != nil) {
-        __AT_PUT_(info, @symbol(negativeSignPosition), val);
+	__AT_PUT_(info, @symbol(negativeSignPosition), val);
     }
 %}.
     ^ info
@@ -8665,8 +8578,8 @@
 
 getNetworkAddresses
     "return a dictionary filled with
-        key -> name of interface
-        value -> the network adsress (as SocketAddress)
+	key -> name of interface
+	value -> the network adsress (as SocketAddress)
      for each interface
     "
 
@@ -8687,21 +8600,21 @@
     DWORD dwStatus;
 
     dwStatus = GetAdaptersInfo(
-                            AdapterInfo,                 // [out] buffer to receive data
-                            &dwBufLen);                  // [in] size of receive data buffer
+			    AdapterInfo,                 // [out] buffer to receive data
+			    &dwBufLen);                  // [in] size of receive data buffer
     if (dwStatus == ERROR_SUCCESS) {
-        PIP_ADAPTER_INFO pAdapterInfo = AdapterInfo;
-        unsigned char *bP;
-        int nA = 0;
-
-        bP = __byteArrayVal(rawData);
-        do {
-            name = __MKSTRING(pAdapterInfo->AdapterName);
-            description = __MKSTRING(pAdapterInfo->Description);
-            macAddress = __MKBYTEARRAY(pAdapterInfo->Address, 6);
-            ipAddress = __MKSTRING(pAdapterInfo->IpAddressList.IpAddress.String);
-            ipAddressMask = __MKSTRING(pAdapterInfo->IpAddressList.IpMask.String);
-            entry = __ARRAY_NEW_INT(5);
+	PIP_ADAPTER_INFO pAdapterInfo = AdapterInfo;
+	unsigned char *bP;
+	int nA = 0;
+
+	bP = __byteArrayVal(rawData);
+	do {
+	    name = __MKSTRING(pAdapterInfo->AdapterName);
+	    description = __MKSTRING(pAdapterInfo->Description);
+	    macAddress = __MKBYTEARRAY(pAdapterInfo->Address, 6);
+	    ipAddress = __MKSTRING(pAdapterInfo->IpAddressList.IpAddress.String);
+	    ipAddressMask = __MKSTRING(pAdapterInfo->IpAddressList.IpMask.String);
+	    entry = __ARRAY_NEW_INT(5);
 
 /*
  * back to ST/X's String definition
@@ -8712,35 +8625,35 @@
 # ifdef __DEF_String
 #  define Context __DEF_Context
 # endif
-            __ArrayInstPtr(entry)->a_element[0] = name; __STORE(entry, name);
-            __ArrayInstPtr(entry)->a_element[1] = description; __STORE(entry, description);
-            __ArrayInstPtr(entry)->a_element[2] = macAddress; __STORE(entry, macAddress);
-            __ArrayInstPtr(entry)->a_element[3] = ipAddress; __STORE(entry, ipAddress);
-            __ArrayInstPtr(entry)->a_element[4] = ipAddressMask; __STORE(entry, ipAddressMask);
-
-            __ArrayInstPtr(rawData)->a_element[nA] = entry; __STORE(rawData, entry);
-            nA++;
-            pAdapterInfo = pAdapterInfo->Next;
-        } while(pAdapterInfo);
-        nAdapters = __mkSmallInteger(nA);
+	    __ArrayInstPtr(entry)->a_element[0] = name; __STORE(entry, name);
+	    __ArrayInstPtr(entry)->a_element[1] = description; __STORE(entry, description);
+	    __ArrayInstPtr(entry)->a_element[2] = macAddress; __STORE(entry, macAddress);
+	    __ArrayInstPtr(entry)->a_element[3] = ipAddress; __STORE(entry, ipAddress);
+	    __ArrayInstPtr(entry)->a_element[4] = ipAddressMask; __STORE(entry, ipAddressMask);
+
+	    __ArrayInstPtr(rawData)->a_element[nA] = entry; __STORE(rawData, entry);
+	    nA++;
+	    pAdapterInfo = pAdapterInfo->Next;
+	} while(pAdapterInfo);
+	nAdapters = __mkSmallInteger(nA);
     }
 %}.
     "Keep the order as returned by the OS"
     info := OrderedDictionary new:nAdapters ? 0.
     nAdapters notNil ifTrue:[
-        1 to:nAdapters do:[:i |
-            |entry name description macAddr ipAddr|
-
-            entry := rawData at:i.
-            name := entry at:1.
-            "/ description := entry at:2.
-            ipAddr := entry at:4.
-            ipAddr := IPSocketAddress addressString:ipAddr.
-            "take the first name"
-            (ipAddr hostAddress contains:[:b| b ~~ 0]) ifTrue:[
-                info at:name ifAbsentPut:ipAddr.
-            ]
-        ].
+	1 to:nAdapters do:[:i |
+	    |entry name description macAddr ipAddr|
+
+	    entry := rawData at:i.
+	    name := entry at:1.
+	    "/ description := entry at:2.
+	    ipAddr := entry at:4.
+	    ipAddr := IPSocketAddress addressString:ipAddr.
+	    "take the first name"
+	    (ipAddr hostAddress contains:[:b| b ~~ 0]) ifTrue:[
+		info at:name ifAbsentPut:ipAddr.
+	    ]
+	].
     ].
     ^ info
 
@@ -8751,8 +8664,8 @@
 
 getNetworkMACAddresses
     "return a dictionary filled with
-        key -> name of interface
-        value -> the MAC adress (as ByteArray)
+	key -> name of interface
+	value -> the MAC adress (as ByteArray)
      for each interface
     "
 
@@ -8773,21 +8686,21 @@
     DWORD dwStatus;
 
     dwStatus = GetAdaptersInfo(
-                            AdapterInfo,                 // [out] buffer to receive data
-                            &dwBufLen);                  // [in] size of receive data buffer
+			    AdapterInfo,                 // [out] buffer to receive data
+			    &dwBufLen);                  // [in] size of receive data buffer
     if (dwStatus == ERROR_SUCCESS) {
-        PIP_ADAPTER_INFO pAdapterInfo = AdapterInfo;
-        unsigned char *bP;
-        int nA = 0;
-
-        bP = __byteArrayVal(rawData);
-        do {
-            name = __MKSTRING(pAdapterInfo->AdapterName);
-            description = __MKSTRING(pAdapterInfo->Description);
-            macAddress = __MKBYTEARRAY(pAdapterInfo->Address, 6);
-            ipAddress = __MKSTRING(pAdapterInfo->IpAddressList.IpAddress.String);
-            ipAddressMask = __MKSTRING(pAdapterInfo->IpAddressList.IpMask.String);
-            entry = __ARRAY_NEW_INT(5);
+	PIP_ADAPTER_INFO pAdapterInfo = AdapterInfo;
+	unsigned char *bP;
+	int nA = 0;
+
+	bP = __byteArrayVal(rawData);
+	do {
+	    name = __MKSTRING(pAdapterInfo->AdapterName);
+	    description = __MKSTRING(pAdapterInfo->Description);
+	    macAddress = __MKBYTEARRAY(pAdapterInfo->Address, 6);
+	    ipAddress = __MKSTRING(pAdapterInfo->IpAddressList.IpAddress.String);
+	    ipAddressMask = __MKSTRING(pAdapterInfo->IpAddressList.IpMask.String);
+	    entry = __ARRAY_NEW_INT(5);
 
 /*
  * back to ST/X's String definition
@@ -8798,32 +8711,32 @@
 # ifdef __DEF_String
 #  define Context __DEF_Context
 # endif
-            __ArrayInstPtr(entry)->a_element[0] = name; __STORE(entry, name);
-            __ArrayInstPtr(entry)->a_element[1] = description; __STORE(entry, description);
-            __ArrayInstPtr(entry)->a_element[2] = macAddress; __STORE(entry, macAddress);
-            __ArrayInstPtr(entry)->a_element[3] = ipAddress; __STORE(entry, ipAddress);
-            __ArrayInstPtr(entry)->a_element[4] = ipAddressMask; __STORE(entry, ipAddressMask);
-
-            __ArrayInstPtr(rawData)->a_element[nA] = entry; __STORE(rawData, entry);
-            nA++;
-            pAdapterInfo = pAdapterInfo->Next;
-        } while(pAdapterInfo);
-        nAdapters = __mkSmallInteger(nA);
+	    __ArrayInstPtr(entry)->a_element[0] = name; __STORE(entry, name);
+	    __ArrayInstPtr(entry)->a_element[1] = description; __STORE(entry, description);
+	    __ArrayInstPtr(entry)->a_element[2] = macAddress; __STORE(entry, macAddress);
+	    __ArrayInstPtr(entry)->a_element[3] = ipAddress; __STORE(entry, ipAddress);
+	    __ArrayInstPtr(entry)->a_element[4] = ipAddressMask; __STORE(entry, ipAddressMask);
+
+	    __ArrayInstPtr(rawData)->a_element[nA] = entry; __STORE(rawData, entry);
+	    nA++;
+	    pAdapterInfo = pAdapterInfo->Next;
+	} while(pAdapterInfo);
+	nAdapters = __mkSmallInteger(nA);
     }
 %}.
     "Keep the order as reurned by the OS"
     info := OrderedDictionary new:nAdapters ? 0.
     nAdapters notNil ifTrue:[
-        1 to:nAdapters do:[:i |
-            |entry name description macAddr ipAddr|
-
-            entry := rawData at:i.
-            name := entry at:1.
-            "/ description := entry at:2.
-            macAddr := entry at:3.
-            "/ ipAddr := entry at:4.
-            info at:name put:macAddr.
-        ].
+	1 to:nAdapters do:[:i |
+	    |entry name description macAddr ipAddr|
+
+	    entry := rawData at:i.
+	    name := entry at:1.
+	    "/ description := entry at:2.
+	    macAddr := entry at:3.
+	    "/ ipAddr := entry at:4.
+	    info at:name put:macAddr.
+	].
     ].
     ^ info
 
@@ -8836,14 +8749,14 @@
     "answer the number of physical processors in the system"
 
 %{
-        SYSTEM_INFO sInfo;
-        GetSystemInfo(&sInfo);
-
-        return __mkSmallInteger(sInfo.dwNumberOfProcessors);
-%}.
-
-    "
-        self getNumberOfProcessors
+	SYSTEM_INFO sInfo;
+	GetSystemInfo(&sInfo);
+
+	return __mkSmallInteger(sInfo.dwNumberOfProcessors);
+%}.
+
+    "
+	self getNumberOfProcessors
     "
 !
 
@@ -8866,7 +8779,7 @@
     "if supported by the OS, return the systemID;
      a unique per machine identification.
      WARNING:
-        not all systems support this; on some, 'unknown' is returned."
+	not all systems support this; on some, 'unknown' is returned."
 
     |regKey systemId|
 
@@ -8882,36 +8795,36 @@
 #endif
 #if defined(HAS_SYSINFO) && defined(SI_HW_SERIAL)
     {
-        char buffer[128];
-
-        buffer[0] = 0;
-        if (sysinfo(SI_HW_SERIAL, buffer, sizeof(buffer))) {
-            buffer[127] = 0;
-            if (strlen(buffer) > 0) {
-                RETURN(__MKSTRING(buffer));
-            }
-        }
-    }
-#endif
-%}.
-
-    regKey := self registryEntry 
-        key:'HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Windows NT\CurrentVersion'.
+	char buffer[128];
+
+	buffer[0] = 0;
+	if (sysinfo(SI_HW_SERIAL, buffer, sizeof(buffer))) {
+	    buffer[127] = 0;
+	    if (strlen(buffer) > 0) {
+		RETURN(__MKSTRING(buffer));
+	    }
+	}
+    }
+#endif
+%}.
+
+    regKey := self registryEntry
+	key:'HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Windows NT\CurrentVersion'.
 
     regKey notNil ifTrue:[
-        systemId := regKey valueNamed:'ProductId'.
-        systemId isNil ifTrue:[
-            regKey := self registryEntry 
-                key:'HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Windows NT\CurrentVersion'
-                flags:#KEY_WOW64_64KEY createIfAbsent:false.
-            systemId := regKey valueNamed:'ProductId'.
-        ].
-    ].
-                                     
+	systemId := regKey valueNamed:'ProductId'.
+	systemId isNil ifTrue:[
+	    regKey := self registryEntry
+		key:'HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Windows NT\CurrentVersion'
+		flags:#KEY_WOW64_64KEY createIfAbsent:false.
+	    systemId := regKey valueNamed:'ProductId'.
+	].
+    ].
+
     ^ systemId ? 'unknown'
 
     "
-     OperatingSystem getSystemID    
+     OperatingSystem getSystemID
     "
 !
 
@@ -8928,25 +8841,25 @@
        This method is mainly provided to augment error reports with some system
        information.
        (in case of system/version specific OS errors, conditional workarounds and patches
-        may be based upon this info).
+	may be based upon this info).
        Your application should NOT depend upon this in any way.
 
      The returned info may (or may not) contain:
-        #system -> some operating system identification (irix, Linux, nt, win32s ...)
-        #version -> OS version (some os version identification)
-        #release -> OS release (3.5, 1.2.1 ...)
-        #node   -> some host identification (hostname)
-        #domain  -> domain name (hosts domain)
-        #machine -> type of machine (i586, mips ...)
+	#system -> some operating system identification (irix, Linux, nt, win32s ...)
+	#version -> OS version (some os version identification)
+	#release -> OS release (3.5, 1.2.1 ...)
+	#node   -> some host identification (hostname)
+	#domain  -> domain name (hosts domain)
+	#machine -> type of machine (i586, mips ...)
 
      win32:
-        #physicalRam -> total amount of physical memory
-        #freeRam -> amount of free memory
-        #swapSize -> size of swapSpace (page file)
-        #freeSwap -> free bytes in swapSpace
-        #virtualRam -> total amount of virtual memory
-        #freeVirtual -> amount of free virtual memory
-        #memoryLoad -> percentage of memory usage (useless)
+	#physicalRam -> total amount of physical memory
+	#freeRam -> amount of free memory
+	#swapSize -> size of swapSpace (page file)
+	#freeSwap -> free bytes in swapSpace
+	#virtualRam -> total amount of virtual memory
+	#freeVirtual -> amount of free virtual memory
+	#memoryLoad -> percentage of memory usage (useless)
     "
 
     |sys node rel ver minorVer majorVer mach dom info arch
@@ -8972,23 +8885,23 @@
     majorVer = __mkSmallInteger(verMajor);
 
     if (HIWORD(vsn) & 0x8000) {
-        sys = @symbol(win95);
+	sys = @symbol(win95);
     } else {
-        if ((verMajor > 5)
-         || ((verMajor == 5) && (verMinor >= 1))) {
-            sys = @symbol(xp);
-            if (verMajor >= 6) {
-                sys = @symbol(vista);
-                if (verMinor >= 1) {
-                    sys = @symbol(win7);
-                    if (verMinor >= 2) {
-                        sys = @symbol(win8);
-                    }
-                }
-            }
-        } else {
-            sys = @symbol(nt);
-        }
+	if ((verMajor > 5)
+	 || ((verMajor == 5) && (verMinor >= 1))) {
+	    sys = @symbol(xp);
+	    if (verMajor >= 6) {
+		sys = @symbol(vista);
+		if (verMinor >= 1) {
+		    sys = @symbol(win7);
+		    if (verMinor >= 2) {
+			sys = @symbol(win8);
+		    }
+		}
+	    }
+	} else {
+	    sys = @symbol(nt);
+	}
     }
     len = snprintf(vsnBuffer, sizeof(vsnBuffer), "%d.%d", verMajor, verMinor);
     rel = __MKSTRING_L(vsnBuffer, len);
@@ -9014,205 +8927,205 @@
 #endif
     {
 #ifdef PROCESSOR_ARCHITECTURE_INTEL
-        case PROCESSOR_ARCHITECTURE_INTEL:
-            arch = @symbol(intel);
-            break;
+	case PROCESSOR_ARCHITECTURE_INTEL:
+	    arch = @symbol(intel);
+	    break;
 #endif
 #ifdef PROCESSOR_ARCHITECTURE_AMD64
-        case PROCESSOR_ARCHITECTURE_AMD64:
-            arch = @symbol(x64);
-            break;
+	case PROCESSOR_ARCHITECTURE_AMD64:
+	    arch = @symbol(x64);
+	    break;
 #endif
 #ifdef PROCESSOR_ARCHITECTURE_MIPS
-        case PROCESSOR_ARCHITECTURE_MIPS:
-            arch = @symbol(mips);
-            break;
+	case PROCESSOR_ARCHITECTURE_MIPS:
+	    arch = @symbol(mips);
+	    break;
 #endif
 #ifdef PROCESSOR_ARCHITECTURE_ALPHA
-        case PROCESSOR_ARCHITECTURE_ALPHA:
-            arch = @symbol(alpha);
-            break;
+	case PROCESSOR_ARCHITECTURE_ALPHA:
+	    arch = @symbol(alpha);
+	    break;
 #endif
 #ifdef PROCESSOR_ARCHITECTURE_ALPHA64
-        case PROCESSOR_ARCHITECTURE_ALPHA64:
-            arch = @symbol(alpha64);
-            break;
+	case PROCESSOR_ARCHITECTURE_ALPHA64:
+	    arch = @symbol(alpha64);
+	    break;
 #endif
 #ifdef PROCESSOR_ARCHITECTURE_PPC
-        case PROCESSOR_ARCHITECTURE_PPC:
-            arch = @symbol(ppc);
-            break;
+	case PROCESSOR_ARCHITECTURE_PPC:
+	    arch = @symbol(ppc);
+	    break;
 #endif
 #ifdef PROCESSOR_ARCHITECTURE_ARM
-        case PROCESSOR_ARCHITECTURE_ARM:
-            arch = @symbol(arm);
-            break;
+	case PROCESSOR_ARCHITECTURE_ARM:
+	    arch = @symbol(arm);
+	    break;
 #endif
 #ifdef PROCESSOR_ARCHITECTURE_SHX
-        case PROCESSOR_ARCHITECTURE_SHX:
-            arch = @symbol(shx);
-            break;
+	case PROCESSOR_ARCHITECTURE_SHX:
+	    arch = @symbol(shx);
+	    break;
 #endif
 #ifdef PROCESSOR_ARCHITECTURE_IA64
-        case PROCESSOR_ARCHITECTURE_IA64:
-            arch = @symbol(ia64);
-            break;
+	case PROCESSOR_ARCHITECTURE_IA64:
+	    arch = @symbol(ia64);
+	    break;
 #endif
 #ifdef PROCESSOR_ARCHITECTURE_MSIL
-        case PROCESSOR_ARCHITECTURE_MSIL:
-            arch = @symbol(msil);
-            break;
+	case PROCESSOR_ARCHITECTURE_MSIL:
+	    arch = @symbol(msil);
+	    break;
 #endif
 #ifdef PROCESSOR_ARCHITECTURE_IA32_ON_WIN64
-        case PROCESSOR_ARCHITECTURE_IA32_ON_WIN64:
-            arch = @symbol(ia32_on_win64);
-            break;
-#endif
-        default:
-            arch = @symbol(unknown);
-            break;
+	case PROCESSOR_ARCHITECTURE_IA32_ON_WIN64:
+	    arch = @symbol(ia32_on_win64);
+	    break;
+#endif
+	default:
+	    arch = @symbol(unknown);
+	    break;
     }
 
     switch (sysInfo.dwProcessorType) {
 #ifdef PROCESSOR_INTEL_386
-        case PROCESSOR_INTEL_386:
-            mach = @symbol(i386);
-            break;
+	case PROCESSOR_INTEL_386:
+	    mach = @symbol(i386);
+	    break;
 #endif
 #ifdef PROCESSOR_INTEL_486
-        case PROCESSOR_INTEL_486:
-            mach = @symbol(i486);
-            break;
+	case PROCESSOR_INTEL_486:
+	    mach = @symbol(i486);
+	    break;
 #endif
 #ifdef PROCESSOR_INTEL_PENTIUM
-        case PROCESSOR_INTEL_PENTIUM:
-            mach = @symbol(i586);
-            break;
+	case PROCESSOR_INTEL_PENTIUM:
+	    mach = @symbol(i586);
+	    break;
 #endif
 #ifdef PROCESSOR_INTEL_860
-        case PROCESSOR_INTEL_860:
-            mach = @symbol(i860);
-            break;
+	case PROCESSOR_INTEL_860:
+	    mach = @symbol(i860);
+	    break;
 #endif
 #ifdef PROCESSOR_INTEL_IA64
-        case PROCESSOR_INTEL_IA64:
-            mach = @symbol(ia64);
-            break;
+	case PROCESSOR_INTEL_IA64:
+	    mach = @symbol(ia64);
+	    break;
 #endif
 #ifdef PROCESSOR_AMD_X8664
-        case PROCESSOR_AMD_X8664:
-            mach = @symbol(x86_64);
-            break;
+	case PROCESSOR_AMD_X8664:
+	    mach = @symbol(x86_64);
+	    break;
 #endif
 #ifdef PROCESSOR_MIPS_R2000
-        case PROCESSOR_MIPS_R2000:
-            mach = @symbol(r2000);
-            break;
+	case PROCESSOR_MIPS_R2000:
+	    mach = @symbol(r2000);
+	    break;
 #endif
 #ifdef PROCESSOR_MIPS_R3000
-        case PROCESSOR_MIPS_R3000:
-            mach = @symbol(r3000);
-            break;
+	case PROCESSOR_MIPS_R3000:
+	    mach = @symbol(r3000);
+	    break;
 #endif
 #ifdef PROCESSOR_MIPS_R4000
-        case PROCESSOR_MIPS_R4000:
-            mach = @symbol(r4000);
-            break;
+	case PROCESSOR_MIPS_R4000:
+	    mach = @symbol(r4000);
+	    break;
 #endif
 #ifdef PROCESSOR_ALPHA_21064
-        case PROCESSOR_ALPHA_21064:
-            mach = @symbol(alpha21064);
-            break;
+	case PROCESSOR_ALPHA_21064:
+	    mach = @symbol(alpha21064);
+	    break;
 #endif
 #ifdef PROCESSOR_ARM720
-        case PROCESSOR_ARM720:
-            mach = @symbol(arm720);
-            break;
+	case PROCESSOR_ARM720:
+	    mach = @symbol(arm720);
+	    break;
 #endif
 #ifdef PROCESSOR_ARM820
-        case PROCESSOR_ARM820:
-            mach = @symbol(arm820);
-            break;
+	case PROCESSOR_ARM820:
+	    mach = @symbol(arm820);
+	    break;
 #endif
 #ifdef PROCESSOR_ARM920
-        case PROCESSOR_ARM920:
-            mach = @symbol(arm920);
-            break;
+	case PROCESSOR_ARM920:
+	    mach = @symbol(arm920);
+	    break;
 #endif
 #ifdef PROCESSOR_ARM_7TDMI
-        case PROCESSOR_ARM_7TDMI:
-            mach = @symbol(arm70001);
-            break;
+	case PROCESSOR_ARM_7TDMI:
+	    mach = @symbol(arm70001);
+	    break;
 #endif
 #ifdef PROCESSOR_STRONGARM
-        case PROCESSOR_STRONGARM:
-            mach = @symbol(strongarm);
-            break;
+	case PROCESSOR_STRONGARM:
+	    mach = @symbol(strongarm);
+	    break;
 #endif
 #ifdef PROCESSOR_PPC_601
-        case PROCESSOR_PPC_601:
-            mach = @symbol(ppc601);
-            break;
+	case PROCESSOR_PPC_601:
+	    mach = @symbol(ppc601);
+	    break;
 #endif
 #ifdef PROCESSOR_PPC_603
-        case PROCESSOR_PPC_603:
-            mach = @symbol(ppc603);
-            break;
+	case PROCESSOR_PPC_603:
+	    mach = @symbol(ppc603);
+	    break;
 #endif
 #ifdef PROCESSOR_PPC_604
-        case PROCESSOR_PPC_604:
-            mach = @symbol(ppc604);
-            break;
+	case PROCESSOR_PPC_604:
+	    mach = @symbol(ppc604);
+	    break;
 #endif
 #ifdef PROCESSOR_PPC_620
-        case PROCESSOR_PPC_620:
-            mach = @symbol(ppc620);
-            break;
+	case PROCESSOR_PPC_620:
+	    mach = @symbol(ppc620);
+	    break;
 #endif
 #ifdef PROCESSOR_HITACHI_SH3
-        case PROCESSOR_HITACHI_SH3:
-            mach = @symbol(sh3);
-            break;
+	case PROCESSOR_HITACHI_SH3:
+	    mach = @symbol(sh3);
+	    break;
 #endif
 #ifdef PROCESSOR_HITACHI_SH3E
-        case PROCESSOR_HITACHI_SH3E:
-            mach = @symbol(sh3e);
-            break;
+	case PROCESSOR_HITACHI_SH3E:
+	    mach = @symbol(sh3e);
+	    break;
 #endif
 #ifdef PROCESSOR_HITACHI_SH4
-        case PROCESSOR_HITACHI_SH4:
-            mach = @symbol(sh4);
-            break;
+	case PROCESSOR_HITACHI_SH4:
+	    mach = @symbol(sh4);
+	    break;
 #endif
 #ifdef PROCESSOR_MOTOROLA_821
-        case PROCESSOR_MOTOROLA_821:
-            mach = @symbol(mc821);
-            break;
+	case PROCESSOR_MOTOROLA_821:
+	    mach = @symbol(mc821);
+	    break;
 #endif
 #ifdef PROCESSOR_SHx_SH3
-        case PROCESSOR_SHx_SH3:
-            mach = @symbol(shx_sh3);
-            break;
+	case PROCESSOR_SHx_SH3:
+	    mach = @symbol(shx_sh3);
+	    break;
 #endif
 #ifdef PROCESSOR_SHx_SH4
-        case PROCESSOR_SHx_SH4:
-            mach = @symbol(shx_sh4);
-            break;
-#endif
-
-        default:
-            sprintf(vsnBuffer, "%d", sysInfo.dwProcessorType);
-            mach =  __MKSTRING(vsnBuffer);
-            break;
+	case PROCESSOR_SHx_SH4:
+	    mach = @symbol(shx_sh4);
+	    break;
+#endif
+
+	default:
+	    sprintf(vsnBuffer, "%d", sysInfo.dwProcessorType);
+	    mach =  __MKSTRING(vsnBuffer);
+	    break;
     }
 
     numberOfCPUs = __MKUINT(sysInfo.dwNumberOfProcessors);
 %}.
     node isNil ifTrue:[
-        node := self getHostName.
+	node := self getHostName.
     ].
     dom isNil ifTrue:[
-        dom := self getDomainName.
+	dom := self getDomainName.
     ].
 
     info := IdentityDictionary new.
@@ -9283,7 +9196,7 @@
     wchar_t buffer[MAXPATHLEN+1];
 
     if (GetWindowsDirectoryW(buffer, MAXPATHLEN)) {
-        RETURN (__mkStringOrU16String_maxlen(buffer, MAXPATHLEN));
+	RETURN (__mkStringOrU16String_maxlen(buffer, MAXPATHLEN));
     }
 %}.
     ^ nil
@@ -9304,7 +9217,7 @@
     wchar_t buffer[MAXPATHLEN+1];
 
     if (GetSystemDirectoryW(buffer, MAXPATHLEN)) {
-        RETURN (__mkStringOrU16String_maxlen(buffer, MAXPATHLEN));
+	RETURN (__mkStringOrU16String_maxlen(buffer, MAXPATHLEN));
     }
 %}.
     ^ nil
@@ -9366,44 +9279,44 @@
     DWORD exitCode;
 
     if (__isExternalAddressLike(processHandleOrPid) ) {
-        processHandle = _HANDLEVal(processHandleOrPid);
-        if (processHandle == 0) {
-            error = @symbol(invalidParameter);
-            goto out;
-        }
+	processHandle = _HANDLEVal(processHandleOrPid);
+	if (processHandle == 0) {
+	    error = @symbol(invalidParameter);
+	    goto out;
+	}
     } else if( __isSmallInteger(processHandleOrPid) ) {
-        // assume, that synchronize needs less privilege...
-        processHandle = processHandleToClose = OpenProcess(SYNCHRONIZE, FALSE, __smallIntegerVal(processHandleOrPid));
-        if (!processHandle) {
-            goto checkError;
-        }
+	// assume, that synchronize needs less privilege...
+	processHandle = processHandleToClose = OpenProcess(SYNCHRONIZE, FALSE, __smallIntegerVal(processHandleOrPid));
+	if (!processHandle) {
+	    goto checkError;
+	}
     } else {
-        error = @symbol(invalidParameter);
-        goto out;
+	error = @symbol(invalidParameter);
+	goto out;
     }
 
     /* check if the handle still refers to a running process */
     if (GetExitCodeProcess(processHandle, &exitCode) != 0) {
-        if (processHandleToClose)
-            CloseHandle(processHandleToClose);
-        if (exitCode == STILL_ACTIVE) {
-            RETURN(true);
-        } else {
-            RETURN(false);
-        }
+	if (processHandleToClose)
+	    CloseHandle(processHandleToClose);
+	if (exitCode == STILL_ACTIVE) {
+	    RETURN(true);
+	} else {
+	    RETURN(false);
+	}
     } else if (processHandleToClose) {
-        CloseHandle(processHandleToClose);
+	CloseHandle(processHandleToClose);
     }
 
 checkError:
     err = GetLastError();
     // we do not have access to the process (so pid does exist ;-))
     if (err == ERROR_ACCESS_DENIED) {
-        RETURN(true);
+	RETURN(true);
     }
     // pid does not exist
     if (err == ERROR_INVALID_PARAMETER) {
-        RETURN(false);
+	RETURN(false);
     }
 
     // any other error - raise signal
@@ -9491,11 +9404,11 @@
 maxFileNameLength
     "return the max number of characters in a filename.
      CAVEAT:
-         Actually, the following is somewhat wrong - some systems
-         support different sizes, depending on the volume.
-         We return a somewhat conservative number here.
-         Another entry, to query for volume specific max
-         will be added in the future."
+	 Actually, the following is somewhat wrong - some systems
+	 support different sizes, depending on the volume.
+	 We return a somewhat conservative number here.
+	 Another entry, to query for volume specific max
+	 will be added in the future."
 
 %{  /* NOCONTEXT */
 
@@ -9528,9 +9441,9 @@
 
     osVersion := OperatingSystem osVersion.
     ^ 'Windows ',
-        (#('2000' 'XP' 'Server2003' 'VISTA' '7' '8')
-            at: (#('5.0' '5.1' '5.2' '6.0' '6.1' '6.2') indexOf:osVersion)
-            ifAbsent:osVersion).
+	(#('2000' 'XP' 'Server2003' 'VISTA' '7' '8')
+	    at: (#('5.0' '5.1' '5.2' '6.0' '6.1' '6.2') indexOf:osVersion)
+	    ifAbsent:osVersion).
 
     "
      self osName
@@ -9571,11 +9484,11 @@
 
 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 this many bytes (max 4) as a SmallInteger.
 
      Return nil on error (and raise PrimitiveFailure).
 
@@ -9593,38 +9506,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: ;
 %}.
@@ -9646,9 +9559,9 @@
 
     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
@@ -9844,10 +9757,10 @@
 
     libDirPath := self stxLibDirPath.
     libDirPath notNil ifTrue:[
-        "/ and also add the libDirPath from the registry ...
-        (sysPath includes:libDirPath) ifFalse:[
-            sysPath add:libDirPath
-        ].
+	"/ and also add the libDirPath from the registry ...
+	(sysPath includes:libDirPath) ifFalse:[
+	    sysPath add:libDirPath
+	].
     ].
 "/    #(
 "/        '\programs\eXept\smalltalk'
@@ -9883,7 +9796,7 @@
 
     k := RegistryEntry key:'HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X\' , Smalltalk versionString.
     k notNil ifTrue:[
-        p := k valueNamed:'BinDir'.
+	p := k valueNamed:'BinDir'.
     ].
     ^ p
 
@@ -9896,17 +9809,17 @@
     "ask the registry for the lib directory"
 
     (Array
-        with:('HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X\' , Smalltalk versionString)
-        with:('HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X'))
+	with:('HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X\' , Smalltalk versionString)
+	with:('HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X'))
     do:[:eachKeyToTry |
-        |k p|
-
-        k := RegistryEntry key:eachKeyToTry.
-        k notNil ifTrue:[
-            p := k valueNamed:'LibDir'.
-            k closeKey.
-            ^ p
-        ].
+	|k p|
+
+	k := RegistryEntry key:eachKeyToTry.
+	k notNil ifTrue:[
+	    p := k valueNamed:'LibDir'.
+	    k closeKey.
+	    ^ p
+	].
     ].
     ^ nil
 
@@ -9982,22 +9895,22 @@
 #define DM_OUT_DEFAULT      DM_UPDATE
 "
     nBytesNeeded := self
-           primDocumentProperties:nil
-           hPrinter:hPrinter
-           pDeviceName: deviceName
-           pDevModeOutput:nil
-           pDevModeInput:nil
-           fMode:0.
+	   primDocumentProperties:nil
+	   hPrinter:hPrinter
+	   pDeviceName: deviceName
+	   pDevModeOutput:nil
+	   pDevModeInput:nil
+	   fMode:0.
 
     devModeOutput := DevModeStructure new:(nBytesNeeded * 2 "never trust MS !!").
 
     rslt := self
-           primDocumentProperties:nil
-           hPrinter:hPrinter
-           pDeviceName: deviceName
-           pDevModeOutput:devModeOutput
-           pDevModeInput:pDevModeInputOrNil
-           fMode:4+2.
+	   primDocumentProperties:nil
+	   hPrinter:hPrinter
+	   pDeviceName: deviceName
+	   pDevModeOutput:devModeOutput
+	   pDevModeInput:pDevModeInputOrNil
+	   fMode:4+2.
 
     ^ devModeOutput
 
@@ -10062,23 +9975,23 @@
 #define DM_OUT_DEFAULT      DM_UPDATE
 "
     nBytesNeeded := self
-           primDocumentProperties:nil
-           hPrinter:hPrinter
-           pDeviceName: deviceName
-           pDevModeOutput:nil
-           pDevModeInput:nil
-           fMode:0.
+	   primDocumentProperties:nil
+	   hPrinter:hPrinter
+	   pDeviceName: deviceName
+	   pDevModeOutput:nil
+	   pDevModeInput:nil
+	   fMode:0.
 
     nBytesNeeded < 0 ifTrue:[^nil].
     devModeOutput := DevModeStructure new:(nBytesNeeded * 2 "never trust MS !!").
 
     rslt := self
-           primDocumentProperties:nil
-           hPrinter:hPrinter
-           pDeviceName: deviceName
-           pDevModeOutput:devModeOutput
-           pDevModeInput:nil
-           fMode:2.
+	   primDocumentProperties:nil
+	   hPrinter:hPrinter
+	   pDeviceName: deviceName
+	   pDevModeOutput:devModeOutput
+	   pDevModeInput:nil
+	   fMode:2.
 
      ^ devModeOutput
 
@@ -10101,19 +10014,19 @@
      sizeBytesArray := ByteArray new:4.
 
      bytesNeeded := self
-                primGetPrinter:hPrinter
-                level:2
-                informationBuffer: nil
-                bufferSize: 0
-                bufferNeededSize:sizeBytesArray.
+		primGetPrinter:hPrinter
+		level:2
+		informationBuffer: nil
+		bufferSize: 0
+		bufferNeededSize:sizeBytesArray.
      bytesNeeded := sizeBytesArray longAt:1.
      informationBuffer := PrinterInfo2Structure new: bytesNeeded.
      rslt := self
-                primGetPrinter:hPrinter
-                level:2
-                informationBuffer:informationBuffer
-                bufferSize: bytesNeeded
-                bufferNeededSize:sizeBytesArray.
+		primGetPrinter:hPrinter
+		level:2
+		informationBuffer:informationBuffer
+		bufferSize: bytesNeeded
+		bufferNeededSize:sizeBytesArray.
      self closePrinter: printerName.
      ^informationBuffer
 
@@ -10133,47 +10046,47 @@
     printerNames := self getPrintersNames.
     collectedInfo := OrderedCollection new.
     printerNames do:[:eachName |
-        |fn vol attributes nm deviceInfo infoFields driverName|
-
-        attributes := Dictionary new.
-
-        fn := eachName asFilename.
-        vol := fn volume.
-        vol notEmptyOrNil ifTrue:[
-            (vol startsWith:'\\') ifTrue:[
-                "/ a remote printer
-                attributes at:#isRemotePrinter put:true.
-                attributes at:#remotePrinterName put:(fn baseName).
-                attributes at:#remotePrinterHost put:(fn directoryName copyFrom:3).
-            ] ifFalse:[
-                "/ some other printer
-            ].
-        ] ifFalse:[
-            "/ some other printer
-        ].
-
-        deviceInfo := self getProfileString:'PrinterPorts' key:eachName default:''.
-        "gives us smething like 'winspool,Ne00:,15,45',
-         which is: driverName, deviceName, ? , ?"
-
-        infoFields := deviceInfo asCollectionOfSubstringsSeparatedBy:$,.
-        driverName := infoFields at:1.
-        2 to: infoFields size by:3 do:[:i |
-            |medium longName|
-
-            medium := infoFields at:i.
-            longName := eachName ,',' , driverName , ',' , medium.
-            attributes at:#driverName put:driverName.
-            attributes at:#longName put:longName.
-            attributes at:#medium put:medium.
-
-            collectedInfo add:
-                (AbstractOperatingSystem::PrinterInfo new
-                    printerName:eachName
-                    attributes:attributes;
-                    setDocumentProperties;
-                    yourself)
-        ].
+	|fn vol attributes nm deviceInfo infoFields driverName|
+
+	attributes := Dictionary new.
+
+	fn := eachName asFilename.
+	vol := fn volume.
+	vol notEmptyOrNil ifTrue:[
+	    (vol startsWith:'\\') ifTrue:[
+		"/ a remote printer
+		attributes at:#isRemotePrinter put:true.
+		attributes at:#remotePrinterName put:(fn baseName).
+		attributes at:#remotePrinterHost put:(fn directoryName copyFrom:3).
+	    ] ifFalse:[
+		"/ some other printer
+	    ].
+	] ifFalse:[
+	    "/ some other printer
+	].
+
+	deviceInfo := self getProfileString:'PrinterPorts' key:eachName default:''.
+	"gives us smething like 'winspool,Ne00:,15,45',
+	 which is: driverName, deviceName, ? , ?"
+
+	infoFields := deviceInfo asCollectionOfSubstringsSeparatedBy:$,.
+	driverName := infoFields at:1.
+	2 to: infoFields size by:3 do:[:i |
+	    |medium longName|
+
+	    medium := infoFields at:i.
+	    longName := eachName ,',' , driverName , ',' , medium.
+	    attributes at:#driverName put:driverName.
+	    attributes at:#longName put:longName.
+	    attributes at:#medium put:medium.
+
+	    collectedInfo add:
+		(AbstractOperatingSystem::PrinterInfo new
+		    printerName:eachName
+		    attributes:attributes;
+		    setDocumentProperties;
+		    yourself)
+	].
     ].
     ^ collectedInfo
 
@@ -10191,7 +10104,7 @@
     |printerNames|
 
     printerNames := (self getProfileString:'PrinterPorts' key:nil default:'')
-                       asCollectionOfSubstringsSeparatedBy:(Character value:0).
+		       asCollectionOfSubstringsSeparatedBy:(Character value:0).
     printerNames := printerNames reject:[:nm | nm isEmpty].
     ^printerNames
 
@@ -10280,12 +10193,12 @@
 
      hPrinter := self openPrinter:'\\http://exept.exept.de:631\lj4' .
      rslt := self
-            primDocumentProperties:nil
-            hPrinter:hPrinter
-            pDeviceName: '\\http://exept.exept.de:631\lj4'
-            pDevModeOutput:nil
-            pDevModeInput:nil
-            fMode:0.
+	    primDocumentProperties:nil
+	    hPrinter:hPrinter
+	    pDeviceName: '\\http://exept.exept.de:631\lj4'
+	    pDevModeOutput:nil
+	    pDevModeInput:nil
+	    fMode:0.
 
      self halt.
     "
@@ -10302,12 +10215,12 @@
 
      hPrinter := self openPrinter:'\\http://exept.exept.de:631\lj4' .
      rslt := self
-            primDocumentProperties:nil
-            hPrinter:hPrinter
-            pDeviceName: '\\http://exept.exept.de:631\lj4'
-            pDevModeOutput:nil
-            pDevModeInput:nil
-            fMode:0.
+	    primDocumentProperties:nil
+	    hPrinter:hPrinter
+	    pDeviceName: '\\http://exept.exept.de:631\lj4'
+	    pDevModeOutput:nil
+	    pDevModeInput:nil
+	    fMode:0.
 
      self halt.
     "
@@ -10324,12 +10237,12 @@
 
      hPrinter := self openPrinter:'\\http://exept.exept.de:631\lj4' .
      rslt := self
-            primDocumentProperties:nil
-            hPrinter:hPrinter
-            pDeviceName: '\\http://exept.exept.de:631\lj4'
-            pDevModeOutput:nil
-            pDevModeInput:nil
-            fMode:0.
+	    primDocumentProperties:nil
+	    hPrinter:hPrinter
+	    pDeviceName: '\\http://exept.exept.de:631\lj4'
+	    pDevModeOutput:nil
+	    pDevModeInput:nil
+	    fMode:0.
 
      self halt.
     "
@@ -10358,20 +10271,20 @@
 
      sizeBytesArray := ByteArray new:4.
      ok := self
-                primGetPrinter:hPrinter
-                level:2
-                informationBuffer: nil
-                bufferSize: 0
-                bufferNeededSize:sizeBytesArray.
+		primGetPrinter:hPrinter
+		level:2
+		informationBuffer: nil
+		bufferSize: 0
+		bufferNeededSize:sizeBytesArray.
      bytesNeeded := sizeBytesArray longAt:1.
 
      informationBuffer := PrinterInfo2Structure new: bytesNeeded.
      rslt := self
-                primGetPrinter:hPrinter
-                level:2
-                informationBuffer:informationBuffer
-                bufferSize: bytesNeeded
-                bufferNeededSize:sizeBytesArray.
+		primGetPrinter:hPrinter
+		level:2
+		informationBuffer:informationBuffer
+		bufferSize: bytesNeeded
+		bufferNeededSize:sizeBytesArray.
      self assert: rslt.
      informationBuffer inspect.
      self closePrinter: printerName.
@@ -10501,9 +10414,9 @@
       'NON'     'no_NO'
       'NOR'     'no_NO'
      ) pairWiseDo:[:key :mappedValue|
-        key = windowsLanguageString ifTrue:[
-            ^ mappedValue
-        ]
+	key = windowsLanguageString ifTrue:[
+	    ^ mappedValue
+	]
     ].
 
     "no mapping"
@@ -10525,21 +10438,21 @@
     if (__isString(inString)
      && __isString(outString)
      && __isSmallInteger(outBufferSize)) {
-        unsigned long c_outBufferSize = __intVal(outBufferSize);
-
-        if (__stringSize(outString) <= c_outBufferSize) {
-            unsigned long c_ret;
-
-            c_ret = ExpandEnvironmentStringsA(__stringVal(inString), __stringVal(outString), c_outBufferSize);
-            RETURN( __mkSmallInteger(c_ret) );
-        }
+	unsigned long c_outBufferSize = __intVal(outBufferSize);
+
+	if (__stringSize(outString) <= c_outBufferSize) {
+	    unsigned long c_ret;
+
+	    c_ret = ExpandEnvironmentStringsA(__stringVal(inString), __stringVal(outString), c_outBufferSize);
+	    RETURN( __mkSmallInteger(c_ret) );
+	}
     }
 %}.
     "/ <apicall: ulongReturn "ExpandEnvironmentStringsA" (pointer pointer ulong) module: "kernel32.dll" >
     ^self primitiveFailed
 
     "
-        self primExpandEnvironmentStringsA:'%ProgramFiles%\test\x' into:(String new:256) inspect size:256
+	self primExpandEnvironmentStringsA:'%ProgramFiles%\test\x' into:(String new:256) inspect size:256
     "
 !
 
@@ -10549,31 +10462,31 @@
     ^self primitiveFailed
 
     "
-        self primExpandEnvironmentStringsW:'%ProgramFiles%\test\x' asUnicodeString into:(Unicode16String new:256) inspect size:256
+	self primExpandEnvironmentStringsW:'%ProgramFiles%\test\x' asUnicodeString into:(Unicode16String new:256) inspect size:256
     "
 ! !
 
 !Win32OperatingSystem class methodsFor:'regional settings'!
 
 country
-        "Answer the current system value for country."
+	"Answer the current system value for country."
 
     ^self queryNationalProfileString: 'iCountry' default: 0
 
     "
-        self country
+	self country
     "
 
     "Modified: / 22-12-2006 / 16:45:32 / User"
 !
 
 countryName
-        "Answer the current system value for country name."
+	"Answer the current system value for country name."
 
     ^self queryNationalProfileString: 'sCountry' default: 'Deutschland'
 
     "
-        self countryName
+	self countryName
     "
 
     "Modified: / 22-12-2006 / 16:45:32 / User"
@@ -10582,8 +10495,8 @@
 dateFormat
     "Answer the current system value for date format.
      Answer DfMDY = Month-Day-Year
-            DfDMY = Day-Month-Year
-            DfYMD = Year-Month-Day."
+	    DfDMY = Day-Month-Year
+	    DfYMD = Year-Month-Day."
 
     |separatorString code|
 
@@ -10605,49 +10518,49 @@
 !
 
 dateFormatCode
-        "Answer the current system value for date format.
-         Answer DfMDY = Month-Day-Year = 0
-                DfDMY = Day-Month-Year = 1
-                DfYMD = Year-Month-Day = 2"
+	"Answer the current system value for date format.
+	 Answer DfMDY = Month-Day-Year = 0
+		DfDMY = Day-Month-Year = 1
+		DfYMD = Year-Month-Day = 2"
 
     ^self queryNationalProfileInt: 'iDate' default: 0
 
     "
-        self dateFormatCode
+	self dateFormatCode
     "
 
     "Modified: / 22-12-2006 / 16:45:53 / User"
 !
 
 dateSeparator
-        "Answer the current system value for date separator."
+	"Answer the current system value for date separator."
 
     ^self queryNationalProfileString: 'sDate' default: '/'
 
     "
-        self dateSeparator
+	self dateSeparator
     "
 
     "Modified: / 22-12-2006 / 16:45:32 / User"
 !
 
 decimalSeparator
-        "Answer the current system value for decimal separator."
+	"Answer the current system value for decimal separator."
 
     ^self queryNationalProfileString: 'sDecimal' default: '.'
 
     "
-        self decimalSeparator
+	self decimalSeparator
     "
 
     "Created: / 22-12-2006 / 16:45:11 / User"
 !
 
 isDateFormatDMY
-        "Answer the current system value for date format.
-         Answer DfMDY = Month-Day-Year
-                DfDMY = Day-Month-Year
-                DfYMD = Year-Month-Day."
+	"Answer the current system value for date format.
+	 Answer DfMDY = Month-Day-Year
+		DfDMY = Day-Month-Year
+		DfYMD = Year-Month-Day."
 
     ^self dateFormatCode = 1
 
@@ -10655,10 +10568,10 @@
 !
 
 isDateFormatMDY
-        "Answer the current system value for date format.
-         Answer DfMDY = Month-Day-Year
-                DfDMY = Day-Month-Year
-                DfYMD = Year-Month-Day."
+	"Answer the current system value for date format.
+	 Answer DfMDY = Month-Day-Year
+		DfDMY = Day-Month-Year
+		DfYMD = Year-Month-Day."
 
     ^self dateFormatCode = 0
 
@@ -10666,10 +10579,10 @@
 !
 
 isDateFormatYMD
-        "Answer the current system value for date format.
-         Answer DfMDY = Month-Day-Year
-                DfDMY = Day-Month-Year
-                DfYMD = Year-Month-Day."
+	"Answer the current system value for date format.
+	 Answer DfMDY = Month-Day-Year
+		DfDMY = Day-Month-Year
+		DfYMD = Year-Month-Day."
 
     ^self dateFormatCode = 2
 
@@ -10677,7 +10590,7 @@
 !
 
 isTimeFormat12Hour
-        "Answer whether the current system time format is 12-hour."
+	"Answer whether the current system time format is 12-hour."
 
     ^self timeFormat = 0
 
@@ -10704,11 +10617,11 @@
 
     | answer |
     answer := self primGetProfileInt: 'Intl'
-        keyName: aKeyName
-        default: -1 asUnsigned32.
+	keyName: aKeyName
+	default: -1 asUnsigned32.
     ^answer = -1 asUnsigned32
-        ifTrue: [ defaultValue ]
-        ifFalse: [ answer ]
+	ifTrue: [ defaultValue ]
+	ifFalse: [ answer ]
 
 "
     self queryNationalProfileInt: 'iDate' default: 0
@@ -10718,43 +10631,43 @@
 !
 
 queryNationalProfileString: aKeyName default: defaultValue
-        "Answer the string value of key aKeyName in
-        the [Intl] application section of the WIN.INI profile file.
-        Answer defaultValue if aKeyName cannot be found."
+	"Answer the string value of key aKeyName in
+	the [Intl] application section of the WIN.INI profile file.
+	Answer defaultValue if aKeyName cannot be found."
     | extString result |
     extString := String new: 80.
     result := self primGetProfileString: 'Intl'
-        keyName: aKeyName
-        default: ''
-        returnedString: extString
-        size: extString size.
+	keyName: aKeyName
+	default: ''
+	returnedString: extString
+	size: extString size.
     ^result > 0
-        ifTrue: [extString copyFrom: 1 to: result]
-        ifFalse: [ defaultValue ]
+	ifTrue: [extString copyFrom: 1 to: result]
+	ifFalse: [ defaultValue ]
 
     "Created: / 22-12-2006 / 16:13:01 / User"
 !
 
 thousandsSeparator
-        "Answer the current system value
-        for the thousands separator."
+	"Answer the current system value
+	for the thousands separator."
 
     ^self queryNationalProfileString: 'sThousand' default: ','
 
     "
-        self thousandsSeparator
+	self thousandsSeparator
     "
 
     "Created: / 22-12-2006 / 16:46:50 / User"
 !
 
 timeFormat
-        "Answer the current system value for time format."
+	"Answer the current system value for time format."
 
     ^self queryNationalProfileInt: 'iTime' default: 0
 
     "
-        self timeFormat
+	self timeFormat
     "
 
     "Created: / 22-12-2006 / 16:48:27 / User"
@@ -10783,29 +10696,29 @@
      This looks for the files extension, and is typically used to present help-files,
      html documents, pdf documents etc.
      operationSymbol is one of:
-        open
-        edit
-        explore
-        print
+	open
+	edit
+	explore
+	print
     "
 
     |handle directoryName|
 
     "nil directory is the current directory"
     directoryStringOrFilenameOrNil notNil ifTrue:[
-        directoryName := directoryStringOrFilenameOrNil asFilename pathName.
+	directoryName := directoryStringOrFilenameOrNil asFilename pathName.
     ].
 
     handle := self
-        shellExecute:nil
-        lpOperation:operationSymbol
-        lpFile:fileOrUrl asString
-        lpParameters:nil
-        lpDirectory:directoryName         
-        nShowCmd:#SW_SHOWNORMAL.
+	shellExecute:nil
+	lpOperation:operationSymbol
+	lpFile:fileOrUrl asString
+	lpParameters:nil
+	lpDirectory:directoryName
+	nShowCmd:#SW_SHOWNORMAL.
 
     handle notNil ifTrue:[
-        handle close.
+	handle close.
     ].
 
 
@@ -10845,27 +10758,27 @@
      I added this in order to be able to shutdown w95 cleanly"
 
     confirmationMessageOrNil notNil ifTrue:[
-        (Dialog confirm:confirmationMessageOrNil) ifFalse:[
-            ^ false
-        ].
+	(Dialog confirm:confirmationMessageOrNil) ifFalse:[
+	    ^ false
+	].
     ].
 %{
     int flag;
 
     if (how == @symbol(shutdown)) {
-        flag = EWX_SHUTDOWN;
+	flag = EWX_SHUTDOWN;
     } else if (how == @symbol(reboot)) {
-        flag = EWX_REBOOT;
+	flag = EWX_REBOOT;
     } else if (how == @symbol(logoff)) {
-        flag = EWX_LOGOFF;
+	flag = EWX_LOGOFF;
     } else if (how == @symbol(forceShutdown)) {
-        flag = EWX_SHUTDOWN | EWX_FORCE;
+	flag = EWX_SHUTDOWN | EWX_FORCE;
     } else if (how == @symbol(forceReboot)) {
-        flag = EWX_REBOOT | EWX_FORCE;
+	flag = EWX_REBOOT | EWX_FORCE;
     } else if (how == @symbol(forceLogoff)) {
-        flag = EWX_LOGOFF | EWX_FORCE;
+	flag = EWX_LOGOFF | EWX_FORCE;
     } else {
-        RETURN (false);
+	RETURN (false);
     }
     RETURN ((ExitWindowsEx(flag, 0) == TRUE) ? true : false);
 %}
@@ -10885,58 +10798,58 @@
      && __bothSmallInteger(d, h)
      && __bothSmallInteger(min, s)
      && __isSmallInteger(millis)) {
-        SYSTEMTIME sysTime;
-        FILETIME fileTime;
-
-        sysTime.wHour = __intVal(h);
-        sysTime.wMinute = __intVal(min);
-        sysTime.wSecond = __intVal(s);
-        sysTime.wMilliseconds = __intVal(millis);
-
-        sysTime.wYear = __intVal(y);
-        sysTime.wMonth = __intVal(m);
-        sysTime.wDay = __intVal(d);
-
-        if (sysTime.wYear < 1602) goto outOfRange;   // not 1601 - so we don't have to care for timezone
-        if (sysTime.wYear > 9999) goto outOfRange;
-
-        if (utcBoolean != true) {
-            // adjust for local time
-
-            // TzSpecificLocalTimeToSystemTime() is not supported in Win2000
-            // - but we do not support Win2k any longer as of 2014
+	SYSTEMTIME sysTime;
+	FILETIME fileTime;
+
+	sysTime.wHour = __intVal(h);
+	sysTime.wMinute = __intVal(min);
+	sysTime.wSecond = __intVal(s);
+	sysTime.wMilliseconds = __intVal(millis);
+
+	sysTime.wYear = __intVal(y);
+	sysTime.wMonth = __intVal(m);
+	sysTime.wDay = __intVal(d);
+
+	if (sysTime.wYear < 1602) goto outOfRange;   // not 1601 - so we don't have to care for timezone
+	if (sysTime.wYear > 9999) goto outOfRange;
+
+	if (utcBoolean != true) {
+	    // adjust for local time
+
+	    // TzSpecificLocalTimeToSystemTime() is not supported in Win2000
+	    // - but we do not support Win2k any longer as of 2014
 #ifdef __BORLANDC__
-            {
-                typedef BOOL (WINAPI *P_TzSpecificLocalTimeToSystemTime)(LPTIME_ZONE_INFORMATION, LPSYSTEMTIME, LPSYSTEMTIME);
-                static P_TzSpecificLocalTimeToSystemTime pTzSpecificLocalTimeToSystemTime;
-
-                if (pTzSpecificLocalTimeToSystemTime == NULL) {
-                    pTzSpecificLocalTimeToSystemTime =
-                        (P_TzSpecificLocalTimeToSystemTime)
-                            GetProcAddress ( GetModuleHandle ("kernel32.dll"),
-                                                              "TzSpecificLocalTimeToSystemTime");
-                }
-                if (!pTzSpecificLocalTimeToSystemTime(0, &sysTime, &sysTime))
-                    goto error;
-            }
-#else
-            if (!TzSpecificLocalTimeToSystemTime(0, &sysTime, &sysTime))
-                goto error;
-#endif
-        }
-
-        if (! SystemTimeToFileTime(&sysTime, &fileTime))
-            goto error;
-
-        osTime = FileTimeToOsTime1970(&fileTime);
+	    {
+		typedef BOOL (WINAPI *P_TzSpecificLocalTimeToSystemTime)(LPTIME_ZONE_INFORMATION, LPSYSTEMTIME, LPSYSTEMTIME);
+		static P_TzSpecificLocalTimeToSystemTime pTzSpecificLocalTimeToSystemTime;
+
+		if (pTzSpecificLocalTimeToSystemTime == NULL) {
+		    pTzSpecificLocalTimeToSystemTime =
+			(P_TzSpecificLocalTimeToSystemTime)
+			    GetProcAddress ( GetModuleHandle ("kernel32.dll"),
+							      "TzSpecificLocalTimeToSystemTime");
+		}
+		if (!pTzSpecificLocalTimeToSystemTime(0, &sysTime, &sysTime))
+		    goto error;
+	    }
+#else
+	    if (!TzSpecificLocalTimeToSystemTime(0, &sysTime, &sysTime))
+		goto error;
+#endif
+	}
+
+	if (! SystemTimeToFileTime(&sysTime, &fileTime))
+	    goto error;
+
+	osTime = FileTimeToOsTime1970(&fileTime);
     }
 outOfRange: ;
 error: ;
 %}.
     osTime notNil ifTrue:[
-        "/ rebias to 1970 by subtracting the number of millis from 1.1.1601 to 1.1.1970
-        "/ ^ osTime - self osTimeOf19700101. -- already done
-        ^ osTime
+	"/ rebias to 1970 by subtracting the number of millis from 1.1.1601 to 1.1.1970
+	"/ ^ osTime - self osTimeOf19700101. -- already done
+	^ osTime
     ].
 
     "Error, some invalid date ot time"
@@ -10989,10 +10902,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?
@@ -11028,8 +10941,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.
@@ -11102,53 +11015,53 @@
     WCHAR nm[33];
 
     if (anIntegerOrNil == nil) {
-        retVal = GetTimeZoneInformation(&tzInfo);
-        switch (retVal) {
-            case TIME_ZONE_ID_STANDARD:
-            case TIME_ZONE_ID_DAYLIGHT:
-            case TIME_ZONE_ID_UNKNOWN:
-                break;
-
-            default:
-            case TIME_ZONE_ID_INVALID:
-                error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
-                goto out;
-        }
+	retVal = GetTimeZoneInformation(&tzInfo);
+	switch (retVal) {
+	    case TIME_ZONE_ID_STANDARD:
+	    case TIME_ZONE_ID_DAYLIGHT:
+	    case TIME_ZONE_ID_UNKNOWN:
+		break;
+
+	    default:
+	    case TIME_ZONE_ID_INVALID:
+		error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
+		goto out;
+	}
     } else if (__isSmallInteger(anIntegerOrNil)) {
-        int year = __intVal(anIntegerOrNil);
+	int year = __intVal(anIntegerOrNil);
 #if defined(__BORLANDC__) || (defined(__MINGW32__) && !defined(__MINGW64__))
-        {
-            typedef BOOL (WINAPI *P_GetTimeZoneInformationForYear)(
-                                        USHORT,
-                                        LPTIME_ZONE_INFORMATION, // - should be, but is not defined: PDYNAMIC_TIME_ZONE_INFORMATION,
-                                        LPTIME_ZONE_INFORMATION);
-            static P_GetTimeZoneInformationForYear pGetTimeZoneInformationForYear;
-            static int haveTriedToGet_P_GetTimeZoneInformationForYear = 0;
-
-            if (! haveTriedToGet_P_GetTimeZoneInformationForYear) {
-                pGetTimeZoneInformationForYear =
-                    (P_GetTimeZoneInformationForYear)GetProcAddress(GetModuleHandle("kernel32.dll"), "GetTimeZoneInformationForYear");
-                haveTriedToGet_P_GetTimeZoneInformationForYear = 1;
-            }
-            if (pGetTimeZoneInformationForYear == NULL) {
-                error = __mkSmallInteger(@symbol(primitiveFailed));
-                goto out;
-            } else {
-                if (!pGetTimeZoneInformationForYear(year, NULL, &tzInfo)) {
-                    error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
-                    goto out;
-                }
-            }
-        }
-#else
-        if (!GetTimeZoneInformationForYear(year, NULL, &tzInfo)) {
-            error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
-            goto out;
-        }
+	{
+	    typedef BOOL (WINAPI *P_GetTimeZoneInformationForYear)(
+					USHORT,
+					LPTIME_ZONE_INFORMATION, // - should be, but is not defined: PDYNAMIC_TIME_ZONE_INFORMATION,
+					LPTIME_ZONE_INFORMATION);
+	    static P_GetTimeZoneInformationForYear pGetTimeZoneInformationForYear;
+	    static int haveTriedToGet_P_GetTimeZoneInformationForYear = 0;
+
+	    if (! haveTriedToGet_P_GetTimeZoneInformationForYear) {
+		pGetTimeZoneInformationForYear =
+		    (P_GetTimeZoneInformationForYear)GetProcAddress(GetModuleHandle("kernel32.dll"), "GetTimeZoneInformationForYear");
+		haveTriedToGet_P_GetTimeZoneInformationForYear = 1;
+	    }
+	    if (pGetTimeZoneInformationForYear == NULL) {
+		error = __mkSmallInteger(@symbol(primitiveFailed));
+		goto out;
+	    } else {
+		if (!pGetTimeZoneInformationForYear(year, NULL, &tzInfo)) {
+		    error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
+		    goto out;
+		}
+	    }
+	}
+#else
+	if (!GetTimeZoneInformationForYear(year, NULL, &tzInfo)) {
+	    error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
+	    goto out;
+	}
 #endif
     } else {
-        error = @symbol(badArgument);
-        goto out;
+	error = @symbol(badArgument);
+	goto out;
     }
 
     bias = __mkSmallInteger(tzInfo.Bias);
@@ -11178,22 +11091,22 @@
 out:;
 %}.
     error notNil ifTrue:[
-        self primitiveFailed:error.
+	self primitiveFailed:error.
     ].
 
     info := self timeZoneInfoClass new.
     info
-        bias:bias
-        name:standardName standardBias:standardBias
-        daylightName:daylightName daylightBias:daylightBias.
+	bias:bias
+	name:standardName standardBias:standardBias
+	daylightName:daylightName daylightBias:daylightBias.
 
     standardDate_m ~~ 0 ifTrue:[
-        info standardYear:standardDate_y standardMonth:standardDate_m standardDay:standardDate_d
-             standardWeekDay:standardDate_wd standardHour:standardDate_h standardMinute:standardDate_min.
+	info standardYear:standardDate_y standardMonth:standardDate_m standardDay:standardDate_d
+	     standardWeekDay:standardDate_wd standardHour:standardDate_h standardMinute:standardDate_min.
     ].
     daylightDate_m ~~ 0 ifTrue:[
-        info daylightYear:daylightDate_y daylightMonth:daylightDate_m daylightDay:daylightDate_d
-             daylightWeekDay:daylightDate_wd daylightHour:daylightDate_h daylightMinute:daylightDate_min.
+	info daylightYear:daylightDate_y daylightMonth:daylightDate_m daylightDay:daylightDate_d
+	     daylightWeekDay:daylightDate_wd daylightHour:daylightDate_h daylightMinute:daylightDate_min.
     ].
 
     ^ info
@@ -11230,8 +11143,8 @@
 %{  /* NOCONTEXT */
 
     if (__isSmallInteger(numberOfSeconds)) {
-        sleep(__intVal(numberOfSeconds));
-        RETURN ( self );
+	sleep(__intVal(numberOfSeconds));
+	RETURN ( self );
     }
 %}.
     "
@@ -11262,115 +11175,115 @@
 
     /* try cache */
     {
-        OBJ lastOsTimeLow, lastOsTimeHi, lastTimeInfo;
-
-        lastOsTimeLow = @global(LastOsTimeLow);
-        lastOsTimeHi = @global(LastOsTimeHi);
-        if (__isInteger(lastOsTimeLow)
-             && (__unsignedLongIntVal(lastOsTimeLow) == __unsignedLongIntVal(tLow))
-             && lastOsTimeHi
-             && (__unsignedLongIntVal(lastOsTimeHi) == __unsignedLongIntVal(tHigh))
-             && (@global(LastTimeInfoIsLocal) == isLocalTime)
-        ) {
-            lastTimeInfo = @global(LastTimeInfo);
-            if (lastTimeInfo != nil) {
-                RETURN (lastTimeInfo);
-            }
-        }
+	OBJ lastOsTimeLow, lastOsTimeHi, lastTimeInfo;
+
+	lastOsTimeLow = @global(LastOsTimeLow);
+	lastOsTimeHi = @global(LastOsTimeHi);
+	if (__isInteger(lastOsTimeLow)
+	     && (__unsignedLongIntVal(lastOsTimeLow) == __unsignedLongIntVal(tLow))
+	     && lastOsTimeHi
+	     && (__unsignedLongIntVal(lastOsTimeHi) == __unsignedLongIntVal(tHigh))
+	     && (@global(LastTimeInfoIsLocal) == isLocalTime)
+	) {
+	    lastTimeInfo = @global(LastTimeInfo);
+	    if (lastTimeInfo != nil) {
+		RETURN (lastTimeInfo);
+	    }
+	}
     }
 
     if (!OsTime1970ToFileTime(tLow, tHigh, &fileTime))
-        goto out;
+	goto out;
     if (!FileTimeToSystemTime(&fileTime, &sysTime))
-        goto out;
+	goto out;
 
     if (isLocalTime == false) { // easy: UTC time
-        sysTimePtr = &sysTime;
-        utcOffset = __mkSmallInteger(0);
-        isDst = false;
+	sysTimePtr = &sysTime;
+	utcOffset = __mkSmallInteger(0);
+	isDst = false;
     } else {  // local time: have to convert and find out about DST
-        TIME_ZONE_INFORMATION tzInfo;
-        LONGLONG longTime;
-        SYSTEMTIME localSysTime;
-        FILETIME localFileTime;
-
-        sysTimePtr = &localSysTime;
-
-        if (!SystemTimeToTzSpecificLocalTime(NULL, &sysTime, &localSysTime))
-            goto out;
-        if (!SystemTimeToFileTime(&localSysTime, &localFileTime))
-            goto out;
-
-        // all the rest is computing the UTC offset and whether DST applies
-        longTime = ((LONGLONG)fileTime.dwHighDateTime << 32) + fileTime.dwLowDateTime;
-        longTime -= ((LONGLONG)localFileTime.dwHighDateTime << 32) + localFileTime.dwLowDateTime;
-
-        // utcOffset is the difference from UTC to local time including possible DST
-        _utcOffset = longTime / 10000000;
-        utcOffset = __mkSmallInteger(_utcOffset);
+	TIME_ZONE_INFORMATION tzInfo;
+	LONGLONG longTime;
+	SYSTEMTIME localSysTime;
+	FILETIME localFileTime;
+
+	sysTimePtr = &localSysTime;
+
+	if (!SystemTimeToTzSpecificLocalTime(NULL, &sysTime, &localSysTime))
+	    goto out;
+	if (!SystemTimeToFileTime(&localSysTime, &localFileTime))
+	    goto out;
+
+	// all the rest is computing the UTC offset and whether DST applies
+	longTime = ((LONGLONG)fileTime.dwHighDateTime << 32) + fileTime.dwLowDateTime;
+	longTime -= ((LONGLONG)localFileTime.dwHighDateTime << 32) + localFileTime.dwLowDateTime;
+
+	// utcOffset is the difference from UTC to local time including possible DST
+	_utcOffset = longTime / 10000000;
+	utcOffset = __mkSmallInteger(_utcOffset);
 
 # if defined(__BORLANDC__) || (defined(__MINGW32__) && !defined(__MINGW64__))
-        {
-            typedef BOOL (WINAPI *P_GetTimeZoneInformationForYear)(
-                                        USHORT,
-                                        LPTIME_ZONE_INFORMATION, // - should be, but is not defined: PDYNAMIC_TIME_ZONE_INFORMATION,
-                                        LPTIME_ZONE_INFORMATION);
-            static P_GetTimeZoneInformationForYear pGetTimeZoneInformationForYear;
-            static int haveTriedToGet_P_GetTimeZoneInformationForYear = 0;
-
-            if (! haveTriedToGet_P_GetTimeZoneInformationForYear) {
-                pGetTimeZoneInformationForYear =
-                    (P_GetTimeZoneInformationForYear)GetProcAddress(GetModuleHandle("kernel32.dll"), "GetTimeZoneInformationForYear");
-                haveTriedToGet_P_GetTimeZoneInformationForYear = 1;
-            }
-            if (pGetTimeZoneInformationForYear == NULL) {
-                // ignore this error and fall back to GetTimeZoneInformation()
-                reason = @symbol(NoGetTimeZoneInformationForYear);
-            } else {
-                if (pGetTimeZoneInformationForYear(localSysTime.wYear, NULL, &tzInfo)) {
-                    _stdUtcOffset = (tzInfo.Bias + tzInfo.StandardBias) * 60;
-                    isDst = (_stdUtcOffset != _utcOffset) ? true : false;
-                } else {
-                    // ignore this error and fall back to GetTimeZoneInformation()
-                    reason = @symbol(GetTimeZoneInformationForYearFailed);
-                    error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
-                }
-            }
-        }
+	{
+	    typedef BOOL (WINAPI *P_GetTimeZoneInformationForYear)(
+					USHORT,
+					LPTIME_ZONE_INFORMATION, // - should be, but is not defined: PDYNAMIC_TIME_ZONE_INFORMATION,
+					LPTIME_ZONE_INFORMATION);
+	    static P_GetTimeZoneInformationForYear pGetTimeZoneInformationForYear;
+	    static int haveTriedToGet_P_GetTimeZoneInformationForYear = 0;
+
+	    if (! haveTriedToGet_P_GetTimeZoneInformationForYear) {
+		pGetTimeZoneInformationForYear =
+		    (P_GetTimeZoneInformationForYear)GetProcAddress(GetModuleHandle("kernel32.dll"), "GetTimeZoneInformationForYear");
+		haveTriedToGet_P_GetTimeZoneInformationForYear = 1;
+	    }
+	    if (pGetTimeZoneInformationForYear == NULL) {
+		// ignore this error and fall back to GetTimeZoneInformation()
+		reason = @symbol(NoGetTimeZoneInformationForYear);
+	    } else {
+		if (pGetTimeZoneInformationForYear(localSysTime.wYear, NULL, &tzInfo)) {
+		    _stdUtcOffset = (tzInfo.Bias + tzInfo.StandardBias) * 60;
+		    isDst = (_stdUtcOffset != _utcOffset) ? true : false;
+		} else {
+		    // ignore this error and fall back to GetTimeZoneInformation()
+		    reason = @symbol(GetTimeZoneInformationForYearFailed);
+		    error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
+		}
+	    }
+	}
 # else
-        if (GetTimeZoneInformationForYear(localSysTime.wYear, NULL, &tzInfo)) {
-            _stdUtcOffset = (tzInfo.Bias + tzInfo.StandardBias) * 60;
-            isDst = (_stdUtcOffset != _utcOffset) ? true : false;
-        } else {
-            // ignore this error and fall back to GetTimeZoneInformation()
-            reason = @symbol(GetTimeZoneInformationForYearFailed);
-            error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
-        }
-# endif
-        // this code is a fallback for WIN XP
-        if (isDst == nil) {
-            DWORD retVal = GetTimeZoneInformation(&tzInfo);
-            switch (retVal) {
-                case TIME_ZONE_ID_STANDARD:
-                case TIME_ZONE_ID_DAYLIGHT:
-                case TIME_ZONE_ID_UNKNOWN:
-                    // nonDstOffset is the difference from UTC to local time without DST
-                    _stdUtcOffset = (tzInfo.Bias + tzInfo.StandardBias) * 60;
-                    isDst = (_stdUtcOffset != _utcOffset) ? true : false;
-                    break;
-
-                // these are errors, which may occur, if the
-                // Windows OS has not been setupm correctly.
-                // We ignore these errors here, but we don't know if DST applies.
-                // Assume that there is no DST.
-                default:
-                case TIME_ZONE_ID_INVALID:
-                    isDst = false;
-                    reason = @symbol(TIME_ZONE_ID_INVALID);
-                    error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
-                    break;
-            }
-        }  // End WINXP backward compatibility
+	if (GetTimeZoneInformationForYear(localSysTime.wYear, NULL, &tzInfo)) {
+	    _stdUtcOffset = (tzInfo.Bias + tzInfo.StandardBias) * 60;
+	    isDst = (_stdUtcOffset != _utcOffset) ? true : false;
+	} else {
+	    // ignore this error and fall back to GetTimeZoneInformation()
+	    reason = @symbol(GetTimeZoneInformationForYearFailed);
+	    error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
+	}
+# endif
+	// this code is a fallback for WIN XP
+	if (isDst == nil) {
+	    DWORD retVal = GetTimeZoneInformation(&tzInfo);
+	    switch (retVal) {
+		case TIME_ZONE_ID_STANDARD:
+		case TIME_ZONE_ID_DAYLIGHT:
+		case TIME_ZONE_ID_UNKNOWN:
+		    // nonDstOffset is the difference from UTC to local time without DST
+		    _stdUtcOffset = (tzInfo.Bias + tzInfo.StandardBias) * 60;
+		    isDst = (_stdUtcOffset != _utcOffset) ? true : false;
+		    break;
+
+		// these are errors, which may occur, if the
+		// Windows OS has not been setupm correctly.
+		// We ignore these errors here, but we don't know if DST applies.
+		// Assume that there is no DST.
+		default:
+		case TIME_ZONE_ID_INVALID:
+		    isDst = false;
+		    reason = @symbol(TIME_ZONE_ID_INVALID);
+		    error = __mkSmallInteger(__WIN32_ERR(GetLastError()));
+		    break;
+	    }
+	}  // End WINXP backward compatibility
     }
 
     hour = __mkSmallInteger(sysTimePtr->wHour);
@@ -11389,22 +11302,22 @@
 "/    '--> REASON: ' errorPrint. reason errorPrintCR. '--> ERROR: ' errorPrint. error errorPrintCR.
 
     year isNil ifTrue:[
-        TimeConversionError raiseErrorString:' - out of range'.
+	TimeConversionError raiseErrorString:' - out of range'.
     ].
 
     info := self timeInfoClass new.
     info
-        year:year
-        month:month
-        day:day
-        hours:hour
-        minutes:minute
-        seconds:second
-        milliseconds:millis
-        utcOffset:utcOffset
-        dst:isDst
-        dayInYear:yDay
-        dayInWeek:weekDay.
+	year:year
+	month:month
+	day:day
+	hours:hour
+	minutes:minute
+	seconds:second
+	milliseconds:millis
+	utcOffset:utcOffset
+	dst:isDst
+	dayInYear:yDay
+	dayInWeek:weekDay.
 
     LastTimeInfo := info.
     LastOsTimeLow := tLow.
@@ -11441,13 +11354,13 @@
 
     appDataDirFromEnv := self getEnvironment:'APPDATA'.
     appDataDirFromEnv notNil ifTrue:[
-        ^ appDataDirFromEnv , '\' , appName
+	^ appDataDirFromEnv , '\' , appName
     ].
     appDataDirFromRegistry :=
-        (self registryEntry key:'HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Explorer\Shell Folders')
-            valueNamed:'AppData'.
+	(self registryEntry key:'HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Explorer\Shell Folders')
+	    valueNamed:'AppData'.
     appDataDirFromRegistry notNil ifTrue:[
-        ^ appDataDirFromRegistry , '\' , appName
+	^ appDataDirFromRegistry , '\' , appName
     ].
     ^ super getApplicationDataDirectoryFor:appName
 
@@ -11466,15 +11379,15 @@
     |dir path|
 
     path := (self registryEntry
-                key:'HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Explorer\Shell Folders')
-            valueNamed:'Desktop'.
+		key:'HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Explorer\Shell Folders')
+	    valueNamed:'Desktop'.
 
     path isNil ifTrue:[
-        "Fallback"
-        dir := self getHomeDirectory.
-        dir isNil ifTrue:[ ^ nil ].
-
-        path := dir , '\Desktop'.
+	"Fallback"
+	dir := self getHomeDirectory.
+	dir isNil ifTrue:[ ^ nil ].
+
+	path := dir , '\Desktop'.
     ].
 
     (self isValidPath:path) ifFalse:[ ^ nil ].
@@ -11495,11 +11408,11 @@
     |dir|
 
     dir := (self registryEntry
-                key:'HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Explorer\Shell Folders')
-            valueNamed:'Personal'.
+		key:'HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Explorer\Shell Folders')
+	    valueNamed:'Personal'.
 
     dir isNil ifTrue:[
-        dir := self getHomeDirectory.
+	dir := self getHomeDirectory.
     ].
 
     ^ dir.
@@ -11548,11 +11461,11 @@
     info := self userInfoOf:userID.
     (info notNil
     and:[info includesKey:#gecos]) ifTrue:[
-        gecos := info at:#gecos.
-        (gecos includes:$,) ifTrue:[
-            ^ gecos copyTo:(gecos indexOf:$,) - 1
-        ].
-        ^ gecos
+	gecos := info at:#gecos.
+	(gecos includes:$,) ifTrue:[
+	    ^ gecos copyTo:(gecos indexOf:$,) - 1
+	].
+	^ gecos
     ].
     ^ self getUserNameFromID:userID
 
@@ -11600,7 +11513,7 @@
 
     dir := self getEnvironment:'USERPROFILE'.
     dir isNil ifTrue:[
-        dir := '.'.
+	dir := '.'.
     ].
     ^ dir.
 
@@ -11625,33 +11538,33 @@
     char *name = (char *)0;
 
     if (firstCall) {
-        DWORD nameSize = sizeof(cachedName);
-
-        if (GetUserName(cachedName, &nameSize) == TRUE) {
-            name = cachedName;
-            firstCall = 0;
-        }
+	DWORD nameSize = sizeof(cachedName);
+
+	if (GetUserName(cachedName, &nameSize) == TRUE) {
+	    name = cachedName;
+	    firstCall = 0;
+	}
     } else {
-        name = cachedName;
+	name = cachedName;
     }
 
     /*
      * try a few common environment variables ...
      */
     if (! name || (name[0] == 0) ) {
-        name = getenv("LOGIN");
-        if (! name || (name[0] == 0) ) {
-            name = getenv("LOGNAME");
-            if (! name || (name[0] == 0) ) {
-                name = getenv("USER");
-            }
-        }
+	name = getenv("LOGIN");
+	if (! name || (name[0] == 0) ) {
+	    name = getenv("LOGNAME");
+	    if (! name || (name[0] == 0) ) {
+		name = getenv("USER");
+	    }
+	}
     }
     /*
      * nope - I really font know who you are.
      */
     if (! name || (name[0] == 0) ) {
-        name = "you";
+	name = "you";
     }
 
     RETURN ( __MKSTRING(name) );
@@ -11680,7 +11593,7 @@
      This is the login name, not the fullName."
 
     aNumber == self getUserID ifTrue:[
-        ^ self getLoginName
+	^ self getLoginName
     ].
 
     ^ '? (' , aNumber printString , ')'
@@ -11705,30 +11618,30 @@
 
     h_Process = GetCurrentProcess();
     if (OpenProcessToken(h_Process,TOKEN_READ,&h_Token) == FALSE) {
-        console_printf("Error: Couldn't open the process token\n");
-        goto getOutOfHere;
+	console_printf("Error: Couldn't open the process token\n");
+	goto getOutOfHere;
     }
     if (GetTokenInformation(h_Token,TokenElevation,&t_TokenElevation,sizeof(t_TokenElevation),&dw_TokenLength) == FALSE) {
-        console_printf("Error: Couldn't retrieve the elevation right of the current process token\n");
-        CloseHandle(h_Token);
-        goto getOutOfHere;
+	console_printf("Error: Couldn't retrieve the elevation right of the current process token\n");
+	CloseHandle(h_Token);
+	goto getOutOfHere;
     }
     if (t_TokenElevation.TokenIsElevated != 0) {
-        if (GetTokenInformation(h_Token,TokenElevationType,&e_ElevationType,sizeof(e_ElevationType),&dw_TokenLength) == FALSE) {
-            console_printf("Error: Couldn't retrieve the elevation token class\n");
-            CloseHandle(h_Token);
-            goto getOutOfHere;
-        } else {
-            if (e_ElevationType == TokenElevationTypeFull || e_ElevationType == TokenElevationTypeDefault) {
-                CloseHandle(h_Token);
-                RETURN(true);
-            }
-            CloseHandle(h_Token);
-            RETURN(false);
-        }
+	if (GetTokenInformation(h_Token,TokenElevationType,&e_ElevationType,sizeof(e_ElevationType),&dw_TokenLength) == FALSE) {
+	    console_printf("Error: Couldn't retrieve the elevation token class\n");
+	    CloseHandle(h_Token);
+	    goto getOutOfHere;
+	} else {
+	    if (e_ElevationType == TokenElevationTypeFull || e_ElevationType == TokenElevationTypeDefault) {
+		CloseHandle(h_Token);
+		RETURN(true);
+	    }
+	    CloseHandle(h_Token);
+	    RETURN(false);
+	}
     } else {
-        CloseHandle(h_Token);
-        RETURN(false);
+	CloseHandle(h_Token);
+	RETURN(false);
     }
 getOutOfHere: ;
 %}.
@@ -11749,22 +11662,22 @@
 
     // Initialize SID.
     if( !AllocateAndInitializeSid( &NtAuthority,
-                                   2,
-                                   SECURITY_BUILTIN_DOMAIN_RID,
-                                   DOMAIN_ALIAS_RID_ADMINS,
-                                   0, 0, 0, 0, 0, 0,
-                                   &AdministratorsGroup))
+				   2,
+				   SECURITY_BUILTIN_DOMAIN_RID,
+				   DOMAIN_ALIAS_RID_ADMINS,
+				   0, 0, 0, 0, 0, 0,
+				   &AdministratorsGroup))
     {
-        // Initializing SID Failed.
-        RETURN( false );
+	// Initializing SID Failed.
+	RETURN( false );
     }
     // Check whether the token is present in admin group.
     if( !CheckTokenMembership( NULL,
-                               AdministratorsGroup,
-                               &IsInAdminGroup ))
+			       AdministratorsGroup,
+			       &IsInAdminGroup ))
     {
-        // Error occurred.
-        IsInAdminGroup = FALSE;
+	// Error occurred.
+	IsInAdminGroup = FALSE;
     }
     // Free SID and return.
     FreeSid(AdministratorsGroup);
@@ -11801,10 +11714,10 @@
     info := IdentityDictionary new.
     loginName := self getLoginName.
     (aNameOrID == self getUserID or:[aNameOrID = loginName]) ifTrue:[
-        userName := loginName.
-        info at:#dir put:self getHomeDirectory.
+	userName := loginName.
+	info at:#dir put:self getHomeDirectory.
     ] ifFalse:[
-        userName := 'unknown'.
+	userName := 'unknown'.
     ].
     info at:#name put:userName.
     "/ uid notNil ifTrue:[info at:#uid put:uid].
@@ -11847,69 +11760,69 @@
     DWORD exitCode;
 
     if (__isExternalAddressLike(pidToWait) ) {
-        HANDLE __pidToWait = _HANDLEVal(pidToWait);
+	HANDLE __pidToWait = _HANDLEVal(pidToWait);
 
 #ifdef PROCESSDEBUG_CHILDPROCESSWAIT
-        console_printf("childProcessWait %x b %d\n",__pidToWait,blocking==true);
-#endif
-
-        if (blocking == true) {
+	console_printf("childProcessWait %x b %d\n",__pidToWait,blocking==true);
+#endif
+
+	if (blocking == true) {
 #ifdef DO_WRAP_CALLS
-            do {
-                __threadErrno = 0;
-                // do not cast to INT - will loose sign bit then!
-                endStatus = STX_API_CALL2( "WaitForSingleObject", WaitForSingleObject, __pidToWait, INFINITE);
-            } while ((endStatus < 0) && (__threadErrno == EINTR));
-#else
-            endStatus = WaitForSingleObject(__pidToWait, INFINITE);
-            if (endStatus < 0) {
-                __threadErrno = __WIN32_ERR(GetLastError());
-            }
-#endif
-            if (endStatus == WAIT_TIMEOUT) {
-                if (blocking==true)
-                    status = @symbol(timeout);
-                else {
-                    status = @symbol(continue);
+	    do {
+		__threadErrno = 0;
+		// do not cast to INT - will loose sign bit then!
+		endStatus = STX_API_CALL2( "WaitForSingleObject", WaitForSingleObject, __pidToWait, INFINITE);
+	    } while ((endStatus < 0) && (__threadErrno == EINTR));
+#else
+	    endStatus = WaitForSingleObject(__pidToWait, INFINITE);
+	    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 if (endStatus == WAIT_OBJECT_0) {
-
-            }
-        }
+		    console_printf("ret nil\n");
+#endif
+		    RETURN(nil);
+		}
+	    } else if (endStatus == WAIT_OBJECT_0) {
+
+	    }
+	}
 
 #ifdef PROCESSDEBUG_CHILDPROCESSWAIT
-        console_printf("GetExitCodeProcess\n");
-#endif
-
-        if (GetExitCodeProcess(__pidToWait, &exitCode)) {
-            if (exitCode == STILL_ACTIVE) {
+	console_printf("GetExitCodeProcess\n");
+#endif
+
+	if (GetExitCodeProcess(__pidToWait, &exitCode)) {
+	    if (exitCode == STILL_ACTIVE) {
 #ifdef PROCESSDEBUG_CHILDPROCESSWAIT
-                console_printf("exitCode: STILL_ACTIVE\n");
-#endif
-                RETURN(nil);
-            }
+		console_printf("exitCode: STILL_ACTIVE\n");
+#endif
+		RETURN(nil);
+	    }
 #ifdef PROCESSDEBUG_CHILDPROCESSWAIT
-            console_printf("exitCode %d\n", exitCode);
-#endif
-            status = @symbol(exit);
-            code = __mkSmallInteger(exitCode);
-            core = false;
-            pid = pidToWait;
-        } else {
-            code = __mkSmallInteger(GetLastError());
+	    console_printf("exitCode %d\n", exitCode);
+#endif
+	    status = @symbol(exit);
+	    code = __mkSmallInteger(exitCode);
+	    core = false;
+	    pid = pidToWait;
+	} else {
+	    code = __mkSmallInteger(GetLastError());
 #ifdef PROCESSDEBUG_CHILDPROCESSWAIT
-            console_printf("GetExitCodeProcess failed: error=%d\n", GetLastError());
-#endif
-        }
+	    console_printf("GetExitCodeProcess failed: error=%d\n", GetLastError());
+#endif
+	}
     }
 %}.
 
     (status isNil or:[pid isNil]) ifTrue:[
-        ^ self primitiveFailed:code
+	^ self primitiveFailed:code
     ].
 
 "/ Transcript show:'pid: '; show:pid; show:' status: '; show:status;
@@ -11925,15 +11838,15 @@
     unsigned long bytes_available;
 
     if (__Class(fd) == @global(Win32SocketHandle)) {
-        if (ioctlsocket((SOCKET)_HANDLEVal(fd), FIONREAD, &bytes_available) == 0) {
-            if (bytes_available > _MAX_INT) bytes_available = _MAX_INT;
-            RETURN(__mkSmallInteger(bytes_available));
-        }
+	if (ioctlsocket((SOCKET)_HANDLEVal(fd), FIONREAD, &bytes_available) == 0) {
+	    if (bytes_available > _MAX_INT) bytes_available = _MAX_INT;
+	    RETURN(__mkSmallInteger(bytes_available));
+	}
     } else if (__isSmallInteger(fd)) {
-        if (PeekNamedPipe(_get_osfhandle(__intVal(fd)), NULL, 0, NULL, &bytes_available, NULL) != 0){
-            if (bytes_available > _MAX_INT) bytes_available = _MAX_INT;
-            RETURN(__mkSmallInteger(bytes_available));
-        }
+	if (PeekNamedPipe(_get_osfhandle(__intVal(fd)), NULL, 0, NULL, &bytes_available, NULL) != 0){
+	    if (bytes_available > _MAX_INT) bytes_available = _MAX_INT;
+	    RETURN(__mkSmallInteger(bytes_available));
+	}
     }
 %}.
 
@@ -11979,53 +11892,53 @@
     int pass = 1;       // perform up to 2 passes
 
     if (readableResultFdArray != nil) {
-        if (! __isArrayLike(readableResultFdArray)) {
-            goto fail;
-        }
-        resultSizeReadable = __arraySize(readableResultFdArray);
+	if (! __isArrayLike(readableResultFdArray)) {
+	    goto fail;
+	}
+	resultSizeReadable = __arraySize(readableResultFdArray);
     }
     if (writableResultFdArray != nil) {
-        if (! __isArrayLike(writableResultFdArray)) {
-            goto fail;
-        }
-        resultSizeWritable = __arraySize(writableResultFdArray);
-        if (readableResultFdArray == writableResultFdArray) {
-            // allow common result set for read/write/except
-            pcntW = &cntR;
-        }
+	if (! __isArrayLike(writableResultFdArray)) {
+	    goto fail;
+	}
+	resultSizeWritable = __arraySize(writableResultFdArray);
+	if (readableResultFdArray == writableResultFdArray) {
+	    // allow common result set for read/write/except
+	    pcntW = &cntR;
+	}
     }
     if (exceptionResultFdArray != nil) {
-        if (! __isArrayLike(exceptionResultFdArray)) {
-            goto fail;
-        }
-        resultSizeException = __arraySize(exceptionResultFdArray);
-        if (exceptionResultFdArray == readableResultFdArray) {
-            // allow common result set for read/write/except
-            pcntE = &cntR;
-        } else if (exceptionResultFdArray == writableResultFdArray) {
-            pcntE = &cntW;
-        }
+	if (! __isArrayLike(exceptionResultFdArray)) {
+	    goto fail;
+	}
+	resultSizeException = __arraySize(exceptionResultFdArray);
+	if (exceptionResultFdArray == readableResultFdArray) {
+	    // allow common result set for read/write/except
+	    pcntE = &cntR;
+	} else if (exceptionResultFdArray == writableResultFdArray) {
+	    pcntE = &cntW;
+	}
     }
 
     if (__isNonNilObject(readFdArray)) {
-        if (! __isArrayLike(readFdArray)) goto fail;
-        readCount = __arraySize(readFdArray);
+	if (! __isArrayLike(readFdArray)) goto fail;
+	readCount = __arraySize(readFdArray);
     } else {
-        readCount = 0;
+	readCount = 0;
     }
 
     if (__isNonNilObject(writeFdArray)) {
-        if (! __isArrayLike(writeFdArray)) goto fail;
-        writeCount = __arraySize(writeFdArray);
+	if (! __isArrayLike(writeFdArray)) goto fail;
+	writeCount = __arraySize(writeFdArray);
     } else {
-        writeCount = 0;
+	writeCount = 0;
     }
 
     if (__isNonNilObject(exceptFdArray)) {
-        if (! __isArrayLike(exceptFdArray)) goto fail;
-        exceptCount = __arraySize(exceptFdArray);
+	if (! __isArrayLike(exceptFdArray)) goto fail;
+	exceptCount = __arraySize(exceptFdArray);
     } else {
-        exceptCount = 0;
+	exceptCount = 0;
     }
 
 pollAgain:
@@ -12035,145 +11948,145 @@
     numHandles = hasSockets = hasPipes = 0;
 
     for (i = 0; (i < readCount) && (numHandles < MAXHANDLE); i++) {
-        OBJ fd = __arrayVal(readFdArray)[i];
-
-        if (fd != nil) {
-            if (__Class(fd) == @global(Win32SocketHandle)) {
-                FD_SET (_HANDLEVal(fd), &readFds);
-                hasSockets++;
-            } else if (__isSmallInteger(fd)) {
-                DWORD canRead;
-                if (PeekNamedPipe(_get_osfhandle(__intVal(fd)), 0, 0, 0, &canRead, 0)) {
-                    if (canRead > 0) {
-                        if (*pcntR < resultSizeReadable) {
-                            __arrayVal(readableResultFdArray)[*pcntR] = fd;
-                        }
-                        (*pcntR)++; cntAll++;
-                    }
-                } else {
-                    @global(LastErrorNumber) = __mkSmallInteger(EBADF);
-                    RETURN (__mkSmallInteger(-1));
-                }
-                hasPipes++;
-            } else {
-                hArray  [numHandles] = _HANDLEVal(fd);
-                retArray[numHandles] = i;
-                ++numHandles;
-            }
-        }
+	OBJ fd = __arrayVal(readFdArray)[i];
+
+	if (fd != nil) {
+	    if (__Class(fd) == @global(Win32SocketHandle)) {
+		FD_SET (_HANDLEVal(fd), &readFds);
+		hasSockets++;
+	    } else if (__isSmallInteger(fd)) {
+		DWORD canRead;
+		if (PeekNamedPipe(_get_osfhandle(__intVal(fd)), 0, 0, 0, &canRead, 0)) {
+		    if (canRead > 0) {
+			if (*pcntR < resultSizeReadable) {
+			    __arrayVal(readableResultFdArray)[*pcntR] = fd;
+			}
+			(*pcntR)++; cntAll++;
+		    }
+		} else {
+		    @global(LastErrorNumber) = __mkSmallInteger(EBADF);
+		    RETURN (__mkSmallInteger(-1));
+		}
+		hasPipes++;
+	    } else {
+		hArray  [numHandles] = _HANDLEVal(fd);
+		retArray[numHandles] = i;
+		++numHandles;
+	    }
+	}
     }
 
     for (i = 0; (i < writeCount) && (numHandles < MAXHANDLE); i++) {
-        OBJ fd = __arrayVal(writeFdArray)[i];
-
-        if (fd != nil) {
-            if (__Class(fd) == @global(Win32SocketHandle)) {
-                FD_SET (_HANDLEVal(fd), &writeFds);
-                hasSockets++;
-            } else if (__isSmallInteger(fd)) {
-                // kludge: assume that pipes can alway be written
-               if (*pcntW < resultSizeWritable) {
-                    __arrayVal(writableResultFdArray)[*pcntW] = fd;
-                }
-                (*pcntW)++; cntAll++;
-                // there is no pipe to check
-            } else {
-                hArray  [numHandles] = _HANDLEVal(fd);
-                retArray[numHandles] = i + 10000;
-                ++numHandles;
-            }
-        }
+	OBJ fd = __arrayVal(writeFdArray)[i];
+
+	if (fd != nil) {
+	    if (__Class(fd) == @global(Win32SocketHandle)) {
+		FD_SET (_HANDLEVal(fd), &writeFds);
+		hasSockets++;
+	    } else if (__isSmallInteger(fd)) {
+		// kludge: assume that pipes can alway be written
+	       if (*pcntW < resultSizeWritable) {
+		    __arrayVal(writableResultFdArray)[*pcntW] = fd;
+		}
+		(*pcntW)++; cntAll++;
+		// there is no pipe to check
+	    } else {
+		hArray  [numHandles] = _HANDLEVal(fd);
+		retArray[numHandles] = i + 10000;
+		++numHandles;
+	    }
+	}
     }
 
     for (i = 0; (i < exceptCount) && (numHandles < MAXHANDLE); i++) {
-        OBJ fdOrPid = __arrayVal(exceptFdArray)[i];
-
-        if (fdOrPid != nil) {
-            if (__Class(fdOrPid) == @global(Win32SocketHandle)) {
-                FD_SET (_HANDLEVal(fdOrPid), &exceptFds);
-                hasSockets++;
-            } else if (__isExternalAddressLike(fdOrPid)) {
-                // a PID
-                hArray  [numHandles] = _HANDLEVal(fdOrPid);
-                retArray[numHandles] = i + 20000;
-                ++numHandles;
-            }
-        }
+	OBJ fdOrPid = __arrayVal(exceptFdArray)[i];
+
+	if (fdOrPid != nil) {
+	    if (__Class(fdOrPid) == @global(Win32SocketHandle)) {
+		FD_SET (_HANDLEVal(fdOrPid), &exceptFds);
+		hasSockets++;
+	    } else if (__isExternalAddressLike(fdOrPid)) {
+		// a PID
+		hArray  [numHandles] = _HANDLEVal(fdOrPid);
+		retArray[numHandles] = i + 20000;
+		++numHandles;
+	    }
+	}
     }
 
     if (hasSockets) {
-        struct timeval tv = {0, 0};
-        int nReady;
+	struct timeval tv = {0, 0};
+	int nReady;
 
 #ifdef SELECT3DEBUGWIN32
-        console_printf("select hasSockets = %d\n", hasSockets);
-#endif
-        nReady = select(1 , &readFds, &writeFds, &exceptFds, &tv);  // first parameter to select is ignored in windows
-        if (nReady < 0) {
+	console_printf("select hasSockets = %d\n", hasSockets);
+#endif
+	nReady = select(1 , &readFds, &writeFds, &exceptFds, &tv);  // first parameter to select is ignored in windows
+	if (nReady < 0) {
 #ifdef SELECTDEBUGWIN32
-            console_printf("error in select %d %d\n", nReady, GetLastError());
-#endif
-            @global(LastErrorNumber) = __mkSmallInteger(EBADF);
-            RETURN (__mkSmallInteger(-1));
-        }
-        if (nReady > 0) {
+	    console_printf("error in select %d %d\n", nReady, GetLastError());
+#endif
+	    @global(LastErrorNumber) = __mkSmallInteger(EBADF);
+	    RETURN (__mkSmallInteger(-1));
+	}
+	if (nReady > 0) {
 #ifdef SELECT3DEBUGWIN32
-            console_printf("select nReady %d of %d\n", nReady, hasSockets);
-#endif
-            for (i = 0; i < readCount; i++) {
-                OBJ fd = __arrayVal(readFdArray)[i];
-                if ((__Class(fd) == @global(Win32SocketHandle)) && FD_ISSET(_HANDLEVal(fd), &readFds)) {
-                    if (*pcntR < resultSizeReadable) {
-                        __arrayVal(readableResultFdArray)[*pcntR] = fd;
-                        __STORE(readableResultFdArray, fd);
-                    }
-                    (*pcntR)++; cntAll++;
-                }
-            }
-            for (i = 0; i < writeCount; i++) {
-                OBJ fd = __arrayVal(writeFdArray)[i];
-                if ((__Class(fd) == @global(Win32SocketHandle)) && FD_ISSET(_HANDLEVal(fd), &writeFds)) {
-                    if (*pcntW < resultSizeWritable) {
-                        __arrayVal(writableResultFdArray)[*pcntW] = fd;
-                        __STORE(writableResultFdArray, fd);
-                    }
-                    (*pcntW)++; cntAll++;
-                }
-            }
-            for (i = 0; i < exceptCount; i++) {
-                OBJ fd = __arrayVal(exceptFdArray)[i];
-                if ((__Class(fd) == @global(Win32SocketHandle)) && FD_ISSET(_HANDLEVal(fd), &exceptFds)) {
-                    if (*pcntE < resultSizeException) {
-                        __arrayVal(exceptionResultFdArray)[*pcntE] = fd;
-                        __STORE(exceptionResultFdArray, fd);
-                    }
-                    (*pcntE)++; cntAll++;
-                }
-            }
-
-        }
+	    console_printf("select nReady %d of %d\n", nReady, hasSockets);
+#endif
+	    for (i = 0; i < readCount; i++) {
+		OBJ fd = __arrayVal(readFdArray)[i];
+		if ((__Class(fd) == @global(Win32SocketHandle)) && FD_ISSET(_HANDLEVal(fd), &readFds)) {
+		    if (*pcntR < resultSizeReadable) {
+			__arrayVal(readableResultFdArray)[*pcntR] = fd;
+			__STORE(readableResultFdArray, fd);
+		    }
+		    (*pcntR)++; cntAll++;
+		}
+	    }
+	    for (i = 0; i < writeCount; i++) {
+		OBJ fd = __arrayVal(writeFdArray)[i];
+		if ((__Class(fd) == @global(Win32SocketHandle)) && FD_ISSET(_HANDLEVal(fd), &writeFds)) {
+		    if (*pcntW < resultSizeWritable) {
+			__arrayVal(writableResultFdArray)[*pcntW] = fd;
+			__STORE(writableResultFdArray, fd);
+		    }
+		    (*pcntW)++; cntAll++;
+		}
+	    }
+	    for (i = 0; i < exceptCount; i++) {
+		OBJ fd = __arrayVal(exceptFdArray)[i];
+		if ((__Class(fd) == @global(Win32SocketHandle)) && FD_ISSET(_HANDLEVal(fd), &exceptFds)) {
+		    if (*pcntE < resultSizeException) {
+			__arrayVal(exceptionResultFdArray)[*pcntE] = fd;
+			__STORE(exceptionResultFdArray, fd);
+		    }
+		    (*pcntE)++; cntAll++;
+		}
+	    }
+
+	}
     }
     if (pass > 1)       // perform maximum 2 passes
-        goto done;
+	goto done;
 
     if (cntAll) {
-        // check for other handles and return immediately, no timeout
-        t = 0;
+	// check for other handles and return immediately, no timeout
+	t = 0;
     } else {
-        if (__isSmallInteger(millis)) {
-            t = __intVal(millis);
-
-            if (t <= 0 && numHandles == 0) {
-                RETURN (__mkSmallInteger(0));
-            }
-        } else {
-            t = INFINITE;
-        }
+	if (__isSmallInteger(millis)) {
+	    t = __intVal(millis);
+
+	    if (t <= 0 && numHandles == 0) {
+		RETURN (__mkSmallInteger(0));
+	    }
+	} else {
+	    t = INFINITE;
+	}
     }
 
     if (numHandles == 0 && t == 0) {
-        // nothing to do and no wait
-        goto done;
+	// nothing to do and no wait
+	goto done;
     }
 
 #ifdef SELECT3DEBUGWIN32
@@ -12184,105 +12097,105 @@
 
     if (res == WAIT_TIMEOUT) {
 #ifdef SELECT3DEBUGWIN32
-        console_printf("- timeOut; ret nil\n" );
-#endif
-        if (t != 0 && (hasSockets || hasPipes)) {
-            // if not a single handle is ready, poll sockets an pipes again
-            pass = 2;
-            goto pollAgain;
-        }
-        goto done;
+	console_printf("- timeOut; ret nil\n" );
+#endif
+	if (t != 0 && (hasSockets || hasPipes)) {
+	    // if not a single handle is ready, poll sockets an pipes again
+	    pass = 2;
+	    goto pollAgain;
+	}
+	goto done;
     }
 
     if (res == WAIT_FAILED) {
 #ifdef SELECT2DEBUGWIN32
-        console_printf("- error %d (last %d); ret -1\n", __threadErrno, GetLastError());
-#endif
-        if (__threadErrno == EINTR) {
-            @global(LastErrorNumber) = nil;
-            RETURN (__mkSmallInteger(0));
-        } else {
-            if (@global(InfoPrinting) == true) {
+	console_printf("- error %d (last %d); ret -1\n", __threadErrno, GetLastError());
+#endif
+	if (__threadErrno == EINTR) {
+	    @global(LastErrorNumber) = nil;
+	    RETURN (__mkSmallInteger(0));
+	} else {
+	    if (@global(InfoPrinting) == true) {
 //                console_fprintf(stderr, "Win32OS [info]: select errno = %d (last %d)\n", __threadErrno, GetLastError());
-                console_printf("Win32OS [info]: select errno = %d (last %d)\n", __threadErrno, GetLastError());
-            }
-            @global(LastErrorNumber) = __mkSmallInteger(EBADF);
-            RETURN (__mkSmallInteger(-1));
-        }
+		console_printf("Win32OS [info]: select errno = %d (last %d)\n", __threadErrno, GetLastError());
+	    }
+	    @global(LastErrorNumber) = __mkSmallInteger(EBADF);
+	    RETURN (__mkSmallInteger(-1));
+	}
     }
 
     if (numHandles) {
-        if (res == numHandles) {
-            // vmwait() added an IRQ event to the handles, and this one has been triggered
-            if (1 /* @global(InfoPrinting) == true */) {
-                console_fprintf(stderr, "Win32OS [info]: plugIn event has been handled\n");
-            }
-            goto done;
-        }
-        if ((res < 0) || (res >= numHandles)) {
-            console_printf("- res=%d error1 %d\n", res, GetLastError());
-            goto done;
-        }
-
-        idx = retArray[res];
-        cntAll++;
+	if (res == numHandles) {
+	    // vmwait() added an IRQ event to the handles, and this one has been triggered
+	    if (1 /* @global(InfoPrinting) == true */) {
+		console_fprintf(stderr, "Win32OS [info]: plugIn event has been handled\n");
+	    }
+	    goto done;
+	}
+	if ((res < 0) || (res >= numHandles)) {
+	    console_printf("- res=%d error1 %d\n", res, GetLastError());
+	    goto done;
+	}
+
+	idx = retArray[res];
+	cntAll++;
 
 #ifdef SELECTDEBUGWIN32
-        console_printf("wait Handles res %d idx %d numHandles %d --- ", res, idx, numHandles);
-#endif
-        if (idx < 10000) {
-            if (*pcntR < resultSizeReadable) {
-                OBJ temp = __arrayVal(readFdArray)[idx];
-                __arrayVal(readableResultFdArray)[*pcntR] = temp;
-                __STORE(readableResultFdArray, temp);
+	console_printf("wait Handles res %d idx %d numHandles %d --- ", res, idx, numHandles);
+#endif
+	if (idx < 10000) {
+	    if (*pcntR < resultSizeReadable) {
+		OBJ temp = __arrayVal(readFdArray)[idx];
+		__arrayVal(readableResultFdArray)[*pcntR] = temp;
+		__STORE(readableResultFdArray, temp);
 #ifdef SELECTDEBUGWIN32
-                console_printf("read ready: %x\n", __externalAddressVal(temp));
-#endif
-                (*pcntR)++;
-            }
-        } else if (idx < 20000) {
-            if (*pcntW < resultSizeWritable) {
-                OBJ temp = __arrayVal(writeFdArray)[idx-10000];
-                __arrayVal(writableResultFdArray)[*pcntW] = temp;
-                __STORE(writableResultFdArray, temp);
+		console_printf("read ready: %x\n", __externalAddressVal(temp));
+#endif
+		(*pcntR)++;
+	    }
+	} else if (idx < 20000) {
+	    if (*pcntW < resultSizeWritable) {
+		OBJ temp = __arrayVal(writeFdArray)[idx-10000];
+		__arrayVal(writableResultFdArray)[*pcntW] = temp;
+		__STORE(writableResultFdArray, temp);
 #ifdef SELECTDEBUGWIN32
-                console_printf("write ready: %x\n", temp);
-#endif
-                (*pcntW)++;
-            }
-        } else {
-            if (*pcntE < resultSizeException) {
-                OBJ temp = __arrayVal(exceptFdArray)[idx-20000];
-                __arrayVal(exceptionResultFdArray)[*pcntE] = temp;
-                __STORE(exceptionResultFdArray, temp);
+		console_printf("write ready: %x\n", temp);
+#endif
+		(*pcntW)++;
+	    }
+	} else {
+	    if (*pcntE < resultSizeException) {
+		OBJ temp = __arrayVal(exceptFdArray)[idx-20000];
+		__arrayVal(exceptionResultFdArray)[*pcntE] = temp;
+		__STORE(exceptionResultFdArray, temp);
 #ifdef SELECTDEBUGWIN32
-                console_printf("except ready: %x\n", temp);
-#endif
-                (*pcntE)++;
-            }
+		console_printf("except ready: %x\n", temp);
+#endif
+		(*pcntE)++;
+	    }
 #ifdef SELECTDEBUGWIN32
-            else
-                console_printf("cntE: %d, resultSizeException: %d\n", *pcntE, resultSizeException);
-#endif
-        }
+	    else
+		console_printf("cntE: %d, resultSizeException: %d\n", *pcntE, resultSizeException);
+#endif
+	}
     }
     if (t != 0 && (hasSockets || hasPipes)) {
-        // back after timeout, maybe some sockets or pipes did wake up
-        // in the meantime?
-        pass = 2;
-        goto pollAgain;
+	// back after timeout, maybe some sockets or pipes did wake up
+	// in the meantime?
+	pass = 2;
+	goto pollAgain;
     }
 
 done:
     /* add a delimiter */
     if (*pcntR < resultSizeReadable) {
-        __arrayVal(readableResultFdArray)[*pcntR] = nil;
+	__arrayVal(readableResultFdArray)[*pcntR] = nil;
     }
     if (*pcntW < resultSizeWritable) {
-        __arrayVal(writableResultFdArray)[*pcntW] = nil;
+	__arrayVal(writableResultFdArray)[*pcntW] = nil;
     }
     if (*pcntE < resultSizeException) {
-        __arrayVal(exceptionResultFdArray)[*pcntE] = nil;
+	__arrayVal(exceptionResultFdArray)[*pcntE] = nil;
     }
 
     @global(LastErrorNumber) = nil;
@@ -12328,59 +12241,59 @@
     INT i, count, hIdx;
 
     if (! __isArrayLike(fdOrHandleArray)) {
-        goto fail;
+	goto fail;
     }
     count = __arraySize(fdOrHandleArray);
 
     for (hIdx=0, i=0; i<count; i++) {
-        OBJ fdOrHandle = __ArrayInstPtr(fdOrHandleArray)->a_element[i];
-        HANDLE h;
-
-        if (fdOrHandle != nil) {
-            if (__isExternalAddressLike(fdOrHandle)) {
-                h = _HANDLEVal(fdOrHandle);
-            } else {
-                if (__isSmallInteger(fdOrHandle)) {
-                    h = (HANDLE) _get_osfhandle (__intVal(fdOrHandle));
-                } else {
-                    goto fail;
-                }
-            }
-            hArray[hIdx] = h;
-            idxArray[hIdx++] = i;
-        }
+	OBJ fdOrHandle = __ArrayInstPtr(fdOrHandleArray)->a_element[i];
+	HANDLE h;
+
+	if (fdOrHandle != nil) {
+	    if (__isExternalAddressLike(fdOrHandle)) {
+		h = _HANDLEVal(fdOrHandle);
+	    } else {
+		if (__isSmallInteger(fdOrHandle)) {
+		    h = (HANDLE) _get_osfhandle (__intVal(fdOrHandle));
+		} else {
+		    goto fail;
+		}
+	    }
+	    hArray[hIdx] = h;
+	    idxArray[hIdx++] = i;
+	}
     }
 
     if (__isSmallInteger(millis)) {
-        t = __intVal(millis);
+	t = __intVal(millis);
     } else {
-        t = INFINITE;
+	t = INFINITE;
     }
 
 #ifdef DO_WRAP_CALLS
     if (t != 0) {
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            res = STX_API_CALL4( "WaitForMultipleObjects", WaitForMultipleObjects, hIdx, hArray, FALSE, t);
-        } while ((res < 0) && (__threadErrno == EINTR));
+	do {
+	    __threadErrno = 0;
+	    // do not cast to INT - will loose sign bit then!
+	    res = STX_API_CALL4( "WaitForMultipleObjects", WaitForMultipleObjects, hIdx, hArray, FALSE, t);
+	} while ((res < 0) && (__threadErrno == EINTR));
     } else
 #endif
     {
-        res = WaitForMultipleObjects(hIdx, hArray, FALSE, t);
-        if (res < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
+	res = WaitForMultipleObjects(hIdx, hArray, FALSE, t);
+	if (res < 0) {
+	    __threadErrno = __WIN32_ERR(GetLastError());
+	}
     }
 
     if (res == WAIT_FAILED) {
-        RETURN (nil);
+	RETURN (nil);
     }
     if (res == WAIT_TIMEOUT) {
-        RETURN (nil);
+	RETURN (nil);
     }
     if ((res >= WAIT_OBJECT_0) && (res < (WAIT_OBJECT_0+hIdx))) {
-        RETURN (__arrayVal(fdOrHandleArray)[idxArray[res-WAIT_OBJECT_0]]);
+	RETURN (__arrayVal(fdOrHandleArray)[idxArray[res-WAIT_OBJECT_0]]);
     }
 
     RETURN (nil);
@@ -12405,38 +12318,38 @@
     HANDLE h = NULL;
 
     if (__isExternalAddressLike(fdOrHandle)) {
-        h = _HANDLEVal(fdOrHandle);
+	h = _HANDLEVal(fdOrHandle);
     } else {
-        if (__isSmallInteger(fdOrHandle)) {
-            h = (HANDLE) _get_osfhandle (__intVal(fdOrHandle));
-        } else {
-            goto fail;
-        }
+	if (__isSmallInteger(fdOrHandle)) {
+	    h = (HANDLE) _get_osfhandle (__intVal(fdOrHandle));
+	} else {
+	    goto fail;
+	}
     }
 
     if (__isSmallInteger(millis)) {
-        t = __intVal(millis);
+	t = __intVal(millis);
     } else {
-        t = INFINITE;
+	t = INFINITE;
     }
 
 #ifdef DO_WRAP_CALLS
     do {
-        __threadErrno = 0;
-        // do not cast to INT - will loose sign bit then!
-        res = STX_API_CALL2( "WaitForSingleObject", WaitForSingleObject, h,  t);
+	__threadErrno = 0;
+	// do not cast to INT - will loose sign bit then!
+	res = STX_API_CALL2( "WaitForSingleObject", WaitForSingleObject, h,  t);
     } while ((res < 0) && (__threadErrno == EINTR));
 #else
     res = WaitForSingleObject(h, t);
     if (res < 0) {
-        __threadErrno = __WIN32_ERR(GetLastError());
+	__threadErrno = __WIN32_ERR(GetLastError());
     }
 #endif
     if (res == WAIT_FAILED) {
-        RETURN (nil);
+	RETURN (nil);
     }
     if (res == WAIT_TIMEOUT) {
-        RETURN (nil);
+	RETURN (nil);
     }
 
     RETURN (fdOrHandle);
@@ -12631,11 +12544,11 @@
 
 type:t mode:m uid:u gid:g size:s id:i accessed:aT modified:mT created:cT sourcePath:lP fullName:fullName alternativeName:name2
     ^ self basicNew
-        type:t mode:m uid:u gid:g size:s
-        id:i accessed:aT modified:mT created:cT
-        sourcePath:lP
-        fullName:fullName
-        alternativeName:name2
+	type:t mode:m uid:u gid:g size:s
+	id:i accessed:aT modified:mT created:cT
+	sourcePath:lP
+	fullName:fullName
+	alternativeName:name2
 ! !
 
 !Win32OperatingSystem::FileStatusInfo methodsFor:'accessing'!
@@ -12656,18 +12569,18 @@
 
     path := self alternativePathName.
     path notNil ifTrue:[
-        idx := path lastIndexOf:$\ startingAt:path size-1.
-        idx ~~ 0 ifTrue:[
-            path := path copyFrom:(idx+1).
-        ].
+	idx := path lastIndexOf:$\ startingAt:path size-1.
+	idx ~~ 0 ifTrue:[
+	    path := path copyFrom:(idx+1).
+	].
     ].
 
     ^ path
 
     "
-        'C:\' asFilename info alternativeName
-        'C:\Dokumente und Einstellungen\' asFilename info alternativeName
-        'C:\Dokumente und Einstellungen' asFilename info alternativeName
+	'C:\' asFilename info alternativeName
+	'C:\Dokumente und Einstellungen\' asFilename info alternativeName
+	'C:\Dokumente und Einstellungen' asFilename info alternativeName
     "
 !
 
@@ -12677,14 +12590,14 @@
 
     "/ access lazily...
     alternativePathName isNil ifTrue:[
-        alternativePathName := (OperatingSystem getShortPathName:sourcePath) asSingleByteString.
+	alternativePathName := (OperatingSystem getShortPathName:sourcePath) asSingleByteString.
     ].
 
     ^ alternativePathName
 
     "
-        'C:\' asFilename info alternativePathName
-        'C:\Dokumente und Einstellungen' asFilename info alternativePathName
+	'C:\' asFilename info alternativePathName
+	'C:\Dokumente und Einstellungen' asFilename info alternativePathName
     "
 !
 
@@ -12708,18 +12621,18 @@
 
     path := self fullPathName.
     path notNil ifTrue:[
-        idx := path lastIndexOf:$\ startingAt:path size-1.
-        idx ~~ 0 ifTrue:[
-            path := path copyFrom:(idx+1).
-        ].
+	idx := path lastIndexOf:$\ startingAt:path size-1.
+	idx ~~ 0 ifTrue:[
+	    path := path copyFrom:(idx+1).
+	].
     ].
 
     ^ path
 
     "
-        '\' asFilename info fullName
-        'C:\' asFilename info fullName
-        'C:\Dokumente und Einstellungen' asFilename info fullName
+	'\' asFilename info fullName
+	'C:\' asFilename info fullName
+	'C:\Dokumente und Einstellungen' asFilename info fullName
     "
 !
 
@@ -12729,14 +12642,14 @@
 
     "/ access lazily...
     fullPathName isNil ifTrue:[
-        fullPathName := OperatingSystem getLongPathName:sourcePath.
+	fullPathName := OperatingSystem getLongPathName:sourcePath.
     ].
 
     ^ fullPathName
 
     "
-        'C:\' asFilename info fullPathName
-        'C:\Dokumente und Einstellungen' asFilename info fullPathName
+	'C:\' asFilename info fullPathName
+	'C:\Dokumente und Einstellungen' asFilename info fullPathName
     "
 !
 
@@ -12757,9 +12670,9 @@
 
     "/ access lazily...
     linkTargetPath isNil ifTrue:[
-        type == #symbolicLink ifTrue:[
-            linkTargetPath := OperatingSystem getLinkTarget:sourcePath.
-        ]
+	type == #symbolicLink ifTrue:[
+	    linkTargetPath := OperatingSystem getLinkTarget:sourcePath.
+	]
     ].
 
     ^ linkTargetPath
@@ -13010,9 +12923,9 @@
 
 isSpecialFile
     ^ (type ~~ #directory
-        and:[type ~~ #remoteDirectory
-        and:[type ~~ #regular
-        and:[type ~~ #symbolicLink
+	and:[type ~~ #remoteDirectory
+	and:[type ~~ #regular
+	and:[type ~~ #symbolicLink
     ]]])
 !
 
@@ -13038,20 +12951,20 @@
 
     [Instance variables:]
 
-        pid     <Integer>       OS-Process identifier
-
-        status  <Symbol>        either #exit #signal #stop #continue
-
-        code    <Integer>       either exitcode or signalnumber
-
-        core    <Boolean>       true if core has been dumped
+	pid     <Integer>       OS-Process identifier
+
+	status  <Symbol>        either #exit #signal #stop #continue
+
+	code    <Integer>       either exitcode or signalnumber
+
+	core    <Boolean>       true if core has been dumped
 
 
     [author:]
-        Stefan Vogel
+	Stefan Vogel
 
     [see also:]
-        OperatingSystem
+	OperatingSystem
 "
 ! !
 
@@ -13200,15 +13113,15 @@
     COFF machine type IDs.
 
     [author:]
-        Jan Vrany
+	Jan Vrany
 
     [instance variables:]
 
     [class variables:]
 
     [see also:]
-        Microsoft Portable Executable and Common Object File Format Specification,
-        section 6. Machine Types
+	Microsoft Portable Executable and Common Object File Format Specification,
+	section 6. Machine Types
 
 "
 ! !
@@ -13268,14 +13181,14 @@
     information about executables / .dlls on Windows
 
     [author:]
-        Jan Vrany <jan.vrany@fit.cvut.cz>
+	Jan Vrany <jan.vrany@fit.cvut.cz>
 
     [instance variables:]
 
     [class variables:]
 
     [see also:]
-        Microsoft Portable Executable and Common Object File Format Specification
+	Microsoft Portable Executable and Common Object File Format Specification
 
 "
 ! !
@@ -13305,24 +13218,24 @@
 initializeOnFile: aStringOrFilename
     file := aStringOrFilename asFilename.
     file exists ifFalse:[
-        self error:'Given file does not exist'.
-        ^ nil
+	self error:'Given file does not exist'.
+	^ nil
     ].
     file isRegularFile ifFalse:[
-        self error:'Given file is not a regular file'.
-        ^ nil
+	self error:'Given file is not a regular file'.
+	^ nil
     ].
     file readingFileDo:[ :s |
-        | sig |
-        s binary.
-        s position: PE_Signature_OFFSET_OFFSET.
-        s position: (s nextUnsignedLongMSB: false).
-        sig := s next: PE_Signature size.
-        sig = PE_Signature ifFalse:[
-            self error: 'Given file is not a valid PE file (no valid PE signature found)'.
-            ^ nil
-        ].
-        data := s next: COFF_HEADER_SIZE
+	| sig |
+	s binary.
+	s position: PE_Signature_OFFSET_OFFSET.
+	s position: (s nextUnsignedLongMSB: false).
+	sig := s next: PE_Signature size.
+	sig = PE_Signature ifFalse:[
+	    self error: 'Given file is not a valid PE file (no valid PE signature found)'.
+	    ^ nil
+	].
+	data := s next: COFF_HEADER_SIZE
     ].
 
     "Created: / 16-03-2015 / 14:34:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -13347,24 +13260,24 @@
 counterIndexTextDictionary
 
     "
-        self counterIndexTextDictionary
+	self counterIndexTextDictionary
     "
 
     CounterIndexTextDictionary isNil ifTrue:[
-        self synchronized:[
-            CounterIndexTextDictionary isNil ifTrue:[
-                |performanceText counterIndexTextDictionary|
-
-                performanceText := self getPerformanceText valueNamed:'Counter'.
-                counterIndexTextDictionary := IdentityDictionary new.
-
-                1 to:performanceText size by:2 do:[:index|
-                    counterIndexTextDictionary at:(performanceText at:index) asInteger put:(performanceText at:index + 1).
-                ].
-
-                CounterIndexTextDictionary := counterIndexTextDictionary.
-            ].
-        ].
+	self synchronized:[
+	    CounterIndexTextDictionary isNil ifTrue:[
+		|performanceText counterIndexTextDictionary|
+
+		performanceText := self getPerformanceText valueNamed:'Counter'.
+		counterIndexTextDictionary := IdentityDictionary new.
+
+		1 to:performanceText size by:2 do:[:index|
+		    counterIndexTextDictionary at:(performanceText at:index) asInteger put:(performanceText at:index + 1).
+		].
+
+		CounterIndexTextDictionary := counterIndexTextDictionary.
+	    ].
+	].
     ].
 
     ^ CounterIndexTextDictionary
@@ -13373,24 +13286,24 @@
 helpIndexTextDictionary
 
     "
-        self helpIndexTextDictionary
+	self helpIndexTextDictionary
     "
 
     HelpIndexTextDictionary isNil ifTrue:[
-        self synchronized:[
-            HelpIndexTextDictionary isNil ifTrue:[
-                |performanceText helpIndexTextDictionary|
-
-                performanceText := self getPerformanceText valueNamed:'Help'.
-                helpIndexTextDictionary := IdentityDictionary new.
-
-                1 to:performanceText size by:2 do:[:index|
-                    helpIndexTextDictionary at:(performanceText at:index) asInteger put:(performanceText at:index + 1).
-                ].
-
-                HelpIndexTextDictionary := helpIndexTextDictionary.
-            ].
-        ].
+	self synchronized:[
+	    HelpIndexTextDictionary isNil ifTrue:[
+		|performanceText helpIndexTextDictionary|
+
+		performanceText := self getPerformanceText valueNamed:'Help'.
+		helpIndexTextDictionary := IdentityDictionary new.
+
+		1 to:performanceText size by:2 do:[:index|
+		    helpIndexTextDictionary at:(performanceText at:index) asInteger put:(performanceText at:index + 1).
+		].
+
+		HelpIndexTextDictionary := helpIndexTextDictionary.
+	    ].
+	].
     ].
 
     ^ HelpIndexTextDictionary
@@ -13427,86 +13340,86 @@
 documentation
 
     "
-        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).
-
-        Um dies zu umgehen:
-
-        To turn off UAC
-
-        1. Click Start, and then click Control Panel.
-        2. In Control Panel, click User Accounts.
-        3. In the User Accounts window, click User Accounts.
-        4. In the User Accounts tasks window, click Turn User Account Control on or off.
-        5. If UAC is currently configured in Admin Approval Mode, the User Account Control message appears. Click Continue.
-        6. Clear the Use User Account Control (UAC) to help protect your computer check box, and then click OK.
-        7. Click Restart Now to apply the change right away, or click Restart Later and close the User Accounts tasks window.
+	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).
+
+	Um dies zu umgehen:
+
+	To turn off UAC
+
+	1. Click Start, and then click Control Panel.
+	2. In Control Panel, click User Accounts.
+	3. In the User Accounts window, click User Accounts.
+	4. In the User Accounts tasks window, click Turn User Account Control on or off.
+	5. If UAC is currently configured in Admin Approval Mode, the User Account Control message appears. Click Continue.
+	6. Clear the Use User Account Control (UAC) to help protect your computer check box, and then click OK.
+	7. Click Restart Now to apply the change right away, or click Restart Later and close the User Accounts tasks window.
     "
 !
 
 examples
 
     "
-        ######################################### PRIMITIVE
-        self getUsedMemoryInPercentage.
-
-        self getPhysicalMemoryInKB.
-        self getPhysicalMemoryInMB.
-
-        self getFreePhysicalMemoryInKB.
-        self getFreePhysicalMemoryInMB.
-
-        self getPageFileSizeInKB.
-        self getPageFileSizeInMB.
-
-        self getFreePageFileSizeInKB.
-        self getFreePageFileSizeInMB.
-
-        self getVirtualMemoryInKB.
-        self getVirtualMemoryInMB.
-
-        ######################################### REGISTRY
-        self helpIndexTextDictionary
-        self counterIndexTextDictionary
-
-        self global getCounterNameIndexArray.
-        self global getObjectNameIndexArray.
-
-        self processor getCounterNameIndexArray.
-        self processor processorUsage.
-        self processor processorUsageFromLast.
-        self processor interruptsPerSecond.
-        self processor interruptsPerSecondFromLast.
-
-        self process getCounterNameIndexArray.
-        self process processUsage.
-        self process processUsageFromLast.
-        self process runningProcesses.
-        self process runningProcessNameList.
-
-        self network getCounterNameIndexArray.
-        self network kBytesReceivedPerSecond.
-        self network kBytesReceivedPerSecondFromLast.
-        self network kBytesSentPerSecond.
-        self network kBytesSentPerSecondFromLast.
-
-        self memory getCounterNameIndexArray.
-        self memory availableMBytes.
-        self memory availableKBytes.
-
-        self diskIO getCounterNameIndexArray.
-        self diskIO diskSpaceFreeInMegaByte.
-        self diskIO diskQueueLength.
-        self diskIO diskTransfersPerSecond.
-        self diskIO diskTransfersPerSecondFromlast.
-        self diskIO diskReadsPerSecond.
-        self diskIO diskReadsPerSecondFromLast.
-        self diskIO diskWritesPerSecond.
-        self diskIO diskWritesPerSecondFromLast.
-        self diskIO diskBytesPerSecond.
-        self diskIO diskBytesPerSecondFromLast.
+	######################################### PRIMITIVE
+	self getUsedMemoryInPercentage.
+
+	self getPhysicalMemoryInKB.
+	self getPhysicalMemoryInMB.
+
+	self getFreePhysicalMemoryInKB.
+	self getFreePhysicalMemoryInMB.
+
+	self getPageFileSizeInKB.
+	self getPageFileSizeInMB.
+
+	self getFreePageFileSizeInKB.
+	self getFreePageFileSizeInMB.
+
+	self getVirtualMemoryInKB.
+	self getVirtualMemoryInMB.
+
+	######################################### REGISTRY
+	self helpIndexTextDictionary
+	self counterIndexTextDictionary
+
+	self global getCounterNameIndexArray.
+	self global getObjectNameIndexArray.
+
+	self processor getCounterNameIndexArray.
+	self processor processorUsage.
+	self processor processorUsageFromLast.
+	self processor interruptsPerSecond.
+	self processor interruptsPerSecondFromLast.
+
+	self process getCounterNameIndexArray.
+	self process processUsage.
+	self process processUsageFromLast.
+	self process runningProcesses.
+	self process runningProcessNameList.
+
+	self network getCounterNameIndexArray.
+	self network kBytesReceivedPerSecond.
+	self network kBytesReceivedPerSecondFromLast.
+	self network kBytesSentPerSecond.
+	self network kBytesSentPerSecondFromLast.
+
+	self memory getCounterNameIndexArray.
+	self memory availableMBytes.
+	self memory availableKBytes.
+
+	self diskIO getCounterNameIndexArray.
+	self diskIO diskSpaceFreeInMegaByte.
+	self diskIO diskQueueLength.
+	self diskIO diskTransfersPerSecond.
+	self diskIO diskTransfersPerSecondFromlast.
+	self diskIO diskReadsPerSecond.
+	self diskIO diskReadsPerSecondFromLast.
+	self diskIO diskWritesPerSecond.
+	self diskIO diskWritesPerSecondFromLast.
+	self diskIO diskBytesPerSecond.
+	self diskIO diskBytesPerSecondFromLast.
     "
 ! !
 
@@ -13515,7 +13428,7 @@
 initialize
 
     "
-        self initialize
+	self initialize
     "
 
     PerformanceText := CounterIndexTextDictionary := HelpIndexTextDictionary := nil.
@@ -13526,7 +13439,7 @@
 getPerformanceText
 
     PerformanceText isNil ifTrue:[
-        PerformanceText := Win32OperatingSystem registryEntry key:'HKEY_PERFORMANCE_TEXT'.
+	PerformanceText := Win32OperatingSystem registryEntry key:'HKEY_PERFORMANCE_TEXT'.
     ].
 
     ^ PerformanceText
@@ -13538,16 +13451,16 @@
     |ret|
 
     %{
-        MEMORYSTATUS mState;
-        GlobalMemoryStatus (&mState);
-
-        ret = __mkSmallInteger(mState.dwAvailPageFile / 1024);
+	MEMORYSTATUS mState;
+	GlobalMemoryStatus (&mState);
+
+	ret = __mkSmallInteger(mState.dwAvailPageFile / 1024);
     %}.
 
     ^ ret
 
     "
-        self getFreePageFileSizeInKB
+	self getFreePageFileSizeInKB
     "
 !
 
@@ -13555,7 +13468,7 @@
     ^ (self getFreePageFileSizeInKB / 1024) asInteger
 
     "
-        self getFreePageFileSizeInMB
+	self getFreePageFileSizeInMB
     "
 !
 
@@ -13563,16 +13476,16 @@
     |ret|
 
     %{
-        MEMORYSTATUS mState;
-        GlobalMemoryStatus (&mState);
-
-        ret = __mkSmallInteger(mState.dwAvailPhys / 1024);
+	MEMORYSTATUS mState;
+	GlobalMemoryStatus (&mState);
+
+	ret = __mkSmallInteger(mState.dwAvailPhys / 1024);
     %}.
 
     ^ ret
 
     "
-        self getFreePhysicalMemoryInKB
+	self getFreePhysicalMemoryInKB
     "
 !
 
@@ -13580,7 +13493,7 @@
     ^ (self getFreePhysicalMemoryInKB / 1024) asInteger
 
     "
-        self getFreePhysicalMemoryInMB
+	self getFreePhysicalMemoryInMB
     "
 !
 
@@ -13588,7 +13501,7 @@
     ^ self getPageFileSizeInMB * 1024
 
     "
-        self getPageFileSizeInKB
+	self getPageFileSizeInKB
     "
 !
 
@@ -13596,16 +13509,16 @@
     |ret|
 
     %{
-        SYSTEM_INFO sInfo;
-        GetSystemInfo(&sInfo);
-
-        ret = __mkSmallInteger(sInfo.dwPageSize);
+	SYSTEM_INFO sInfo;
+	GetSystemInfo(&sInfo);
+
+	ret = __mkSmallInteger(sInfo.dwPageSize);
     %}.
 
     ^ ret
 
     "
-        self getPageFileSizeInMB
+	self getPageFileSizeInMB
     "
 !
 
@@ -13613,16 +13526,16 @@
     |ret|
 
     %{
-        MEMORYSTATUS mState;
-        GlobalMemoryStatus (&mState);
-
-        ret = __mkSmallInteger(mState.dwTotalPhys / 1024);
+	MEMORYSTATUS mState;
+	GlobalMemoryStatus (&mState);
+
+	ret = __mkSmallInteger(mState.dwTotalPhys / 1024);
     %}.
 
     ^ ret
 
     "
-        self getPhysicalMemoryInKB
+	self getPhysicalMemoryInKB
     "
 !
 
@@ -13630,7 +13543,7 @@
     ^ (self getPhysicalMemoryInKB / 1024) asInteger
 
     "
-        self getPhysicalMemoryInMB
+	self getPhysicalMemoryInMB
     "
 !
 
@@ -13638,16 +13551,16 @@
     |ret|
 
     %{
-        MEMORYSTATUS mState;
-        GlobalMemoryStatus (&mState);
-
-        ret = __mkSmallInteger(mState.dwMemoryLoad);
+	MEMORYSTATUS mState;
+	GlobalMemoryStatus (&mState);
+
+	ret = __mkSmallInteger(mState.dwMemoryLoad);
     %}.
 
     ^ ret
 
     "
-        self getUsedMemoryInPercentage
+	self getUsedMemoryInPercentage
     "
 !
 
@@ -13655,16 +13568,16 @@
     |ret|
 
     %{
-        MEMORYSTATUS mState;
-        GlobalMemoryStatus (&mState);
-
-        ret = __mkSmallInteger(mState.dwTotalVirtual / 1024);
+	MEMORYSTATUS mState;
+	GlobalMemoryStatus (&mState);
+
+	ret = __mkSmallInteger(mState.dwTotalVirtual / 1024);
     %}.
 
     ^ ret
 
     "
-        self getVirtualMemoryInKB
+	self getVirtualMemoryInKB
     "
 !
 
@@ -13672,7 +13585,7 @@
     ^ (self getVirtualMemoryInKB / 1024) asInteger
 
     "
-        self getVirtualMemoryInMB
+	self getVirtualMemoryInMB
     "
 ! !
 
@@ -13742,157 +13655,157 @@
 
     //iterate all following objetcs
     for (objectIterator=0; objectIterator<numObjectTypes; objectIterator++) {
-        //add the st_perObject dictionary to st_objectArray
-        st_perObject = __SSEND0(@global(Dictionary), @symbol(new), 0);
-        __AT_PUT_(st_objectArray, __mkSmallInteger(objectIterator+1), st_perObject);
-
-        //get the object data
-        __AT_PUT_(st_perObject, @symbol(ObjectNameTitleIndex), __mkSmallInteger(perfObjectPtr->ObjectNameTitleIndex));
-        __AT_PUT_(st_perObject, @symbol(DetailLevel), __mkSmallInteger(perfObjectPtr->DetailLevel));
-        __AT_PUT_(st_perObject, @symbol(NumCounters), __mkSmallInteger(perfObjectPtr->NumCounters));
-        __AT_PUT_(st_perObject, @symbol(NumInstances), __mkSmallInteger(perfObjectPtr->NumInstances));
-
-        //setup counter array and initialize its pointer
-        st_counterArray = __ARRAY_NEW_INT(perfObjectPtr->NumCounters);
-        perfCounterPtr = (PERF_COUNTER_DEFINITION *)((char *)perfObjectPtr + perfObjectPtr->HeaderLength);
-
-        //add the st_counterArray to st_perObject dictionary
-        __AT_PUT_(st_perObject, @symbol(Counters), st_counterArray);
-
-        //iterate all following counter definition
-        for (counterIterator=0; counterIterator<perfObjectPtr->NumCounters; counterIterator++) {
-            //add the st_perCounter dictionary to st_counterArray
-            st_perCounter = __SSEND0(@global(Dictionary), @symbol(new), 0);
-            __AT_PUT_(st_counterArray, __mkSmallInteger(counterIterator+1), st_perCounter);
-
-            //get the counter data
-            __AT_PUT_(st_perCounter, @symbol(CounterNameTitleIndex), __mkSmallInteger(perfCounterPtr->CounterNameTitleIndex));
-            __AT_PUT_(st_perCounter, @symbol(CounterTypeBits), __mkSmallInteger(perfCounterPtr->CounterType));
-            __AT_PUT_(st_perCounter, @symbol(CounterSize), __mkSmallInteger(perfCounterPtr->CounterSize));
-            __AT_PUT_(st_perCounter, @symbol(CounterOffset), __mkSmallInteger(perfCounterPtr->CounterOffset));
-
-            //put the counter type size
-            switch (perfCounterPtr->CounterType & PERF_SIZE_MASK) {
-                case PERF_SIZE_DWORD:
-                    __AT_PUT_(st_perCounter, @symbol(SIZE),@symbol(DWORD));
-                    break;
-                case PERF_SIZE_LARGE:
-                    __AT_PUT_(st_perCounter, @symbol(SIZE),@symbol(LARGE));
-                    break;
-                case PERF_SIZE_ZERO:
-                    __AT_PUT_(st_perCounter, @symbol(SIZE),@symbol(ZERO));
-                    break;
-                case PERF_SIZE_VARIABLE_LEN:
-                    __AT_PUT_(st_perCounter, @symbol(SIZE),@symbol(VARIABLE_LEN));
-                    break;
-            }
-            switch (perfCounterPtr->CounterType & PERF_TYPE_MASK) {
-                case PERF_TYPE_NUMBER:
-                    __AT_PUT_(st_perCounter, @symbol(TYPE),@symbol(NUMBER));
-                    switch (perfCounterPtr->CounterType & PERF_NUMBERTYPE_MASK) {
-                        case PERF_NUMBER_HEX:
-                            __AT_PUT_(st_perCounter, @symbol(NUMBER),@symbol(HEX));
-                            break;
-                        case PERF_NUMBER_DECIMAL:
-                            __AT_PUT_(st_perCounter, @symbol(NUMBER),@symbol(DECIMAL));
-                            break;
-                        case PERF_NUMBER_DEC_1000:
-                            __AT_PUT_(st_perCounter, @symbol(NUMBER),@symbol(DEC_1000));
-                            break;
-                    }
-                    break;
-                case PERF_TYPE_COUNTER:
-                    __AT_PUT_(st_perCounter, @symbol(TYPE),@symbol(COUNTER));
-                    switch (perfCounterPtr->CounterType & PERF_COUNTERTYPE_MASK) {
-                        case PERF_COUNTER_VALUE:
-                            __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(VALUE));
-                            break;
-                        case PERF_COUNTER_RATE:
-                            __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(RATE));
-                            break;
-                        case PERF_COUNTER_FRACTION:
-                            __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(FRACTION));
-                            break;
-                        case PERF_COUNTER_BASE:
-                            __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(BASE));
-                            break;
-                        case PERF_COUNTER_ELAPSED:
-                            __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(ELAPSED));
-                            break;
-                        case PERF_COUNTER_QUEUELEN:
-                            __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(QUEUELEN));
-                            break;
-                        case PERF_COUNTER_HISTOGRAM:
-                            __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(HISTOGRAM));
-                            break;
+	//add the st_perObject dictionary to st_objectArray
+	st_perObject = __SSEND0(@global(Dictionary), @symbol(new), 0);
+	__AT_PUT_(st_objectArray, __mkSmallInteger(objectIterator+1), st_perObject);
+
+	//get the object data
+	__AT_PUT_(st_perObject, @symbol(ObjectNameTitleIndex), __mkSmallInteger(perfObjectPtr->ObjectNameTitleIndex));
+	__AT_PUT_(st_perObject, @symbol(DetailLevel), __mkSmallInteger(perfObjectPtr->DetailLevel));
+	__AT_PUT_(st_perObject, @symbol(NumCounters), __mkSmallInteger(perfObjectPtr->NumCounters));
+	__AT_PUT_(st_perObject, @symbol(NumInstances), __mkSmallInteger(perfObjectPtr->NumInstances));
+
+	//setup counter array and initialize its pointer
+	st_counterArray = __ARRAY_NEW_INT(perfObjectPtr->NumCounters);
+	perfCounterPtr = (PERF_COUNTER_DEFINITION *)((char *)perfObjectPtr + perfObjectPtr->HeaderLength);
+
+	//add the st_counterArray to st_perObject dictionary
+	__AT_PUT_(st_perObject, @symbol(Counters), st_counterArray);
+
+	//iterate all following counter definition
+	for (counterIterator=0; counterIterator<perfObjectPtr->NumCounters; counterIterator++) {
+	    //add the st_perCounter dictionary to st_counterArray
+	    st_perCounter = __SSEND0(@global(Dictionary), @symbol(new), 0);
+	    __AT_PUT_(st_counterArray, __mkSmallInteger(counterIterator+1), st_perCounter);
+
+	    //get the counter data
+	    __AT_PUT_(st_perCounter, @symbol(CounterNameTitleIndex), __mkSmallInteger(perfCounterPtr->CounterNameTitleIndex));
+	    __AT_PUT_(st_perCounter, @symbol(CounterTypeBits), __mkSmallInteger(perfCounterPtr->CounterType));
+	    __AT_PUT_(st_perCounter, @symbol(CounterSize), __mkSmallInteger(perfCounterPtr->CounterSize));
+	    __AT_PUT_(st_perCounter, @symbol(CounterOffset), __mkSmallInteger(perfCounterPtr->CounterOffset));
+
+	    //put the counter type size
+	    switch (perfCounterPtr->CounterType & PERF_SIZE_MASK) {
+		case PERF_SIZE_DWORD:
+		    __AT_PUT_(st_perCounter, @symbol(SIZE),@symbol(DWORD));
+		    break;
+		case PERF_SIZE_LARGE:
+		    __AT_PUT_(st_perCounter, @symbol(SIZE),@symbol(LARGE));
+		    break;
+		case PERF_SIZE_ZERO:
+		    __AT_PUT_(st_perCounter, @symbol(SIZE),@symbol(ZERO));
+		    break;
+		case PERF_SIZE_VARIABLE_LEN:
+		    __AT_PUT_(st_perCounter, @symbol(SIZE),@symbol(VARIABLE_LEN));
+		    break;
+	    }
+	    switch (perfCounterPtr->CounterType & PERF_TYPE_MASK) {
+		case PERF_TYPE_NUMBER:
+		    __AT_PUT_(st_perCounter, @symbol(TYPE),@symbol(NUMBER));
+		    switch (perfCounterPtr->CounterType & PERF_NUMBERTYPE_MASK) {
+			case PERF_NUMBER_HEX:
+			    __AT_PUT_(st_perCounter, @symbol(NUMBER),@symbol(HEX));
+			    break;
+			case PERF_NUMBER_DECIMAL:
+			    __AT_PUT_(st_perCounter, @symbol(NUMBER),@symbol(DECIMAL));
+			    break;
+			case PERF_NUMBER_DEC_1000:
+			    __AT_PUT_(st_perCounter, @symbol(NUMBER),@symbol(DEC_1000));
+			    break;
+		    }
+		    break;
+		case PERF_TYPE_COUNTER:
+		    __AT_PUT_(st_perCounter, @symbol(TYPE),@symbol(COUNTER));
+		    switch (perfCounterPtr->CounterType & PERF_COUNTERTYPE_MASK) {
+			case PERF_COUNTER_VALUE:
+			    __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(VALUE));
+			    break;
+			case PERF_COUNTER_RATE:
+			    __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(RATE));
+			    break;
+			case PERF_COUNTER_FRACTION:
+			    __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(FRACTION));
+			    break;
+			case PERF_COUNTER_BASE:
+			    __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(BASE));
+			    break;
+			case PERF_COUNTER_ELAPSED:
+			    __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(ELAPSED));
+			    break;
+			case PERF_COUNTER_QUEUELEN:
+			    __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(QUEUELEN));
+			    break;
+			case PERF_COUNTER_HISTOGRAM:
+			    __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(HISTOGRAM));
+			    break;
 #ifdef PERF_COUNTER_PRECISION
-                        case PERF_COUNTER_PRECISION:
-                            __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(PRECISION));
-                            break;
-#endif
-                    }
-                    break;
-                case PERF_TYPE_TEXT:
-                    __AT_PUT_(st_perCounter, @symbol(TYPE),@symbol(TEXT));
-                    switch (perfCounterPtr->CounterType & PERF_TEXTTYPE_MASK) {
-                        case PERF_TEXT_UNICODE:
-                            __AT_PUT_(st_perCounter, @symbol(TEXT),@symbol(UNICODE));
-                            break;
-                        case PERF_TEXT_ASCII:
-                            __AT_PUT_(st_perCounter, @symbol(TEXT),@symbol(ASCII));
-                            break;
-                    }
-                    break;
-                case PERF_TYPE_ZERO:
-                    __AT_PUT_(st_perCounter, @symbol(TYPE),@symbol(ZERO));
-                    break;
-            }
-
-            //setup the counter pointer to the next counter definition
-            perfCounterPtr = (PERF_COUNTER_DEFINITION *)((char *)perfCounterPtr + perfCounterPtr->ByteLength);
-        }
-
-        //goon dependent on the count of instances
-        if (perfObjectPtr->NumInstances < 1) {
-            perfCounterBlockPtr = (PERF_COUNTER_BLOCK *)(perfCounterPtr);
-            __AT_PUT_(st_perObject, @symbol(RawData), __MKBYTEARRAY(perfCounterBlockPtr, perfCounterBlockPtr->ByteLength));
-        } else {
-            //setup the instance pointer to the end of all counters
-            perfInstancePtr = (PERF_INSTANCE_DEFINITION *)(perfCounterPtr);
-
-            //setup st_instanceArray and add it to st_perObject
-            st_instanceArray = __ARRAY_NEW_INT(perfObjectPtr->NumInstances);
-            __AT_PUT_(st_perObject, @symbol(Instances), st_instanceArray);
-
-            //iterate the instances
-            for (instanceIterator=0; instanceIterator<perfObjectPtr->NumInstances; instanceIterator++) {
-                //setup st_perInstance and add it to st_instanceArray
-                st_perInstance = __SSEND0(@global(Dictionary), @symbol(new), 0);
-                __AT_PUT_(st_instanceArray, __mkSmallInteger(instanceIterator+1), st_perInstance);
-
-                //get the instance data
-                __AT_PUT_(st_perInstance, @symbol(Name), __MKBYTEARRAY((wchar_t *)((BYTE *)perfInstancePtr + perfInstancePtr->NameOffset),perfInstancePtr->NameLength));
-                __AT_PUT_(st_perInstance, @symbol(ParentObjectTitleIndex), __mkSmallInteger(perfInstancePtr->ParentObjectTitleIndex));
-                __AT_PUT_(st_perInstance, @symbol(ParentObjectInstance), __mkSmallInteger(perfInstancePtr->ParentObjectInstance));
-                __AT_PUT_(st_perInstance, @symbol(NameOffset), __mkSmallInteger(perfInstancePtr->NameOffset));
-                __AT_PUT_(st_perInstance, @symbol(NameLength), __mkSmallInteger(perfInstancePtr->NameLength));
-
-                //setup the instance pointer to the its end
-                perfInstancePtr = (PERF_INSTANCE_DEFINITION *)((char *)perfInstancePtr + perfInstancePtr->ByteLength);
-
-                //setup the counter block pointer
-                perfCounterBlockPtr = (PERF_COUNTER_BLOCK *)(perfInstancePtr);
-
-                //get the instance raw data
-                __AT_PUT_(st_perInstance, @symbol(RawData), __MKBYTEARRAY(perfCounterBlockPtr, perfCounterBlockPtr->ByteLength));
-
-                //setup the instance pointer to the next instance
-                perfInstancePtr = (PERF_INSTANCE_DEFINITION *)((char *)perfCounterBlockPtr + perfCounterBlockPtr->ByteLength);
-            }
-        }
-
-        //setup the object pointer to the next object
-        perfObjectPtr = (PERF_OBJECT_TYPE *)((char *)perfObjectPtr + perfObjectPtr->TotalByteLength);
+			case PERF_COUNTER_PRECISION:
+			    __AT_PUT_(st_perCounter, @symbol(COUNTER),@symbol(PRECISION));
+			    break;
+#endif
+		    }
+		    break;
+		case PERF_TYPE_TEXT:
+		    __AT_PUT_(st_perCounter, @symbol(TYPE),@symbol(TEXT));
+		    switch (perfCounterPtr->CounterType & PERF_TEXTTYPE_MASK) {
+			case PERF_TEXT_UNICODE:
+			    __AT_PUT_(st_perCounter, @symbol(TEXT),@symbol(UNICODE));
+			    break;
+			case PERF_TEXT_ASCII:
+			    __AT_PUT_(st_perCounter, @symbol(TEXT),@symbol(ASCII));
+			    break;
+		    }
+		    break;
+		case PERF_TYPE_ZERO:
+		    __AT_PUT_(st_perCounter, @symbol(TYPE),@symbol(ZERO));
+		    break;
+	    }
+
+	    //setup the counter pointer to the next counter definition
+	    perfCounterPtr = (PERF_COUNTER_DEFINITION *)((char *)perfCounterPtr + perfCounterPtr->ByteLength);
+	}
+
+	//goon dependent on the count of instances
+	if (perfObjectPtr->NumInstances < 1) {
+	    perfCounterBlockPtr = (PERF_COUNTER_BLOCK *)(perfCounterPtr);
+	    __AT_PUT_(st_perObject, @symbol(RawData), __MKBYTEARRAY(perfCounterBlockPtr, perfCounterBlockPtr->ByteLength));
+	} else {
+	    //setup the instance pointer to the end of all counters
+	    perfInstancePtr = (PERF_INSTANCE_DEFINITION *)(perfCounterPtr);
+
+	    //setup st_instanceArray and add it to st_perObject
+	    st_instanceArray = __ARRAY_NEW_INT(perfObjectPtr->NumInstances);
+	    __AT_PUT_(st_perObject, @symbol(Instances), st_instanceArray);
+
+	    //iterate the instances
+	    for (instanceIterator=0; instanceIterator<perfObjectPtr->NumInstances; instanceIterator++) {
+		//setup st_perInstance and add it to st_instanceArray
+		st_perInstance = __SSEND0(@global(Dictionary), @symbol(new), 0);
+		__AT_PUT_(st_instanceArray, __mkSmallInteger(instanceIterator+1), st_perInstance);
+
+		//get the instance data
+		__AT_PUT_(st_perInstance, @symbol(Name), __MKBYTEARRAY((wchar_t *)((BYTE *)perfInstancePtr + perfInstancePtr->NameOffset),perfInstancePtr->NameLength));
+		__AT_PUT_(st_perInstance, @symbol(ParentObjectTitleIndex), __mkSmallInteger(perfInstancePtr->ParentObjectTitleIndex));
+		__AT_PUT_(st_perInstance, @symbol(ParentObjectInstance), __mkSmallInteger(perfInstancePtr->ParentObjectInstance));
+		__AT_PUT_(st_perInstance, @symbol(NameOffset), __mkSmallInteger(perfInstancePtr->NameOffset));
+		__AT_PUT_(st_perInstance, @symbol(NameLength), __mkSmallInteger(perfInstancePtr->NameLength));
+
+		//setup the instance pointer to the its end
+		perfInstancePtr = (PERF_INSTANCE_DEFINITION *)((char *)perfInstancePtr + perfInstancePtr->ByteLength);
+
+		//setup the counter block pointer
+		perfCounterBlockPtr = (PERF_COUNTER_BLOCK *)(perfInstancePtr);
+
+		//get the instance raw data
+		__AT_PUT_(st_perInstance, @symbol(RawData), __MKBYTEARRAY(perfCounterBlockPtr, perfCounterBlockPtr->ByteLength));
+
+		//setup the instance pointer to the next instance
+		perfInstancePtr = (PERF_INSTANCE_DEFINITION *)((char *)perfCounterBlockPtr + perfCounterBlockPtr->ByteLength);
+	    }
+	}
+
+	//setup the object pointer to the next object
+	perfObjectPtr = (PERF_OBJECT_TYPE *)((char *)perfObjectPtr + perfObjectPtr->TotalByteLength);
     }
 %}.
     objectArray := st_objectArray.
@@ -13901,61 +13814,61 @@
     perfTime100nSec := st_perfTime100nSec.
 
     getNameBlock := [:i|
-        self class counterIndexTextDictionary at:i ifAbsent:['<<no name>>'].
+	self class counterIndexTextDictionary at:i ifAbsent:['<<no name>>'].
     ].
 
     getCounterValueBlock := [:counter :rawData|
-        |offset counterValue|
-
-        offset := counter at:#CounterOffset.
-        offset >= rawData size ifTrue:[
-            counterValue := nil.
-        ] ifFalse:[
-            (counter at:#SIZE) == #LARGE ifTrue:[
-                counterValue := rawData unsignedLongLongAt:offset + 1 bigEndian:false.
-            ] ifFalse:[
-                (counter at:#SIZE) == #DWORD ifTrue:[
-                    counterValue := rawData unsignedLongAt:offset + 1 bigEndian:false.
-                ] ifFalse:[
-                    self halt:'unhandled counter-size; please check'.
-                ].
-            ].
-        ].
-
-        counterValue
+	|offset counterValue|
+
+	offset := counter at:#CounterOffset.
+	offset >= rawData size ifTrue:[
+	    counterValue := nil.
+	] ifFalse:[
+	    (counter at:#SIZE) == #LARGE ifTrue:[
+		counterValue := rawData unsignedLongLongAt:offset + 1 bigEndian:false.
+	    ] ifFalse:[
+		(counter at:#SIZE) == #DWORD ifTrue:[
+		    counterValue := rawData unsignedLongAt:offset + 1 bigEndian:false.
+		] ifFalse:[
+		    self halt:'unhandled counter-size; please check'.
+		].
+	    ].
+	].
+
+	counterValue
     ].
 
     objectArray do:[:anObject|
-        "setup the object name"
-        anObject at:#ObjectNameTitle put:(getNameBlock value:(anObject at:#ObjectNameTitleIndex)).
-
-        "setup the name and a counter value array to each counter"
-        (anObject at:#Counters) do:[:aCounter|
-            aCounter at:#CounterNameTitle put:(getNameBlock value:(aCounter at:#CounterNameTitleIndex)).
-            aCounter at:#CounterValueArray put:OrderedCollection new.
-        ].
-
-        (anObject at:#NumInstances) < 1 ifTrue:[
-            |rawData|
-
-            rawData := anObject at:#RawData.
-
-            (anObject at:#Counters) do:[:aCounter|
-                (aCounter at:#CounterValueArray) add:(getCounterValueBlock value:aCounter value:rawData).
-            ].
-        ] ifFalse:[
-            (anObject at:#Instances) do:[:anInstance|
-                |rawData|
-
-                rawData := anInstance at:#RawData.
-
-                anInstance at:#Name put:((Unicode16String fromBytes:(anInstance at:#Name) copy swapBytes) copyButLast:1).
-
-                (anObject at:#Counters) do:[:aCounter|
-                    (aCounter at:#CounterValueArray) add:(getCounterValueBlock value:aCounter value:rawData).
-                ].
-            ].
-        ].
+	"setup the object name"
+	anObject at:#ObjectNameTitle put:(getNameBlock value:(anObject at:#ObjectNameTitleIndex)).
+
+	"setup the name and a counter value array to each counter"
+	(anObject at:#Counters) do:[:aCounter|
+	    aCounter at:#CounterNameTitle put:(getNameBlock value:(aCounter at:#CounterNameTitleIndex)).
+	    aCounter at:#CounterValueArray put:OrderedCollection new.
+	].
+
+	(anObject at:#NumInstances) < 1 ifTrue:[
+	    |rawData|
+
+	    rawData := anObject at:#RawData.
+
+	    (anObject at:#Counters) do:[:aCounter|
+		(aCounter at:#CounterValueArray) add:(getCounterValueBlock value:aCounter value:rawData).
+	    ].
+	] ifFalse:[
+	    (anObject at:#Instances) do:[:anInstance|
+		|rawData|
+
+		rawData := anInstance at:#RawData.
+
+		anInstance at:#Name put:((Unicode16String fromBytes:(anInstance at:#Name) copy swapBytes) copyButLast:1).
+
+		(anObject at:#Counters) do:[:aCounter|
+		    (aCounter at:#CounterValueArray) add:(getCounterValueBlock value:aCounter value:rawData).
+		].
+	    ].
+	].
     ].
 
     ^ self
@@ -13966,7 +13879,7 @@
 cachedResults
 
     cachedResults isNil ifTrue:[
-        cachedResults := IdentityDictionary new.
+	cachedResults := IdentityDictionary new.
     ].
 
     ^ cachedResults
@@ -13993,8 +13906,8 @@
 aliveTime
 
     "
-        returns the time a data stays alive, in milliseconds
-        before we push a new call and overwrite the data
+	returns the time a data stays alive, in milliseconds
+	before we push a new call and overwrite the data
     "
 
     ^ self subclassResponsibility
@@ -14017,18 +13930,18 @@
 data
 
     self synchronized:[
-        |lastTS|
-
-        lastTS := self lastTimestamp.
-        lastTS isNil ifTrue:[
-            ^ self dataBasic
-        ] ifFalse:[
-            Timestamp now asMilliseconds - lastTS >= self aliveTime ifTrue:[
-                ^ self dataBasic
-            ] ifFalse:[
-                ^ self lastData
-            ].
-        ].
+	|lastTS|
+
+	lastTS := self lastTimestamp.
+	lastTS isNil ifTrue:[
+	    ^ self dataBasic
+	] ifFalse:[
+	    Timestamp now asMilliseconds - lastTS >= self aliveTime ifTrue:[
+		^ self dataBasic
+	    ] ifFalse:[
+		^ self lastData
+	    ].
+	].
     ].
 !
 
@@ -14052,9 +13965,9 @@
     data := self data.
 
     self indexedNameNumbered == 0 ifTrue:[
-        object := data objectArray at:1 ifAbsent:[debugBlock value:(object at:#ObjectNameTitle)].
+	object := data objectArray at:1 ifAbsent:[debugBlock value:(object at:#ObjectNameTitle)].
     ] ifFalse:[
-        object := data objectArray detect:[:el|(el at:#ObjectNameTitleIndex) == self indexedNameNumbered] ifNone:[self error:'counter not found'].
+	object := data objectArray detect:[:el|(el at:#ObjectNameTitleIndex) == self indexedNameNumbered] ifNone:[self error:'counter not found'].
     ].
 
     ^ (object at:#Counters) collect:[:el|Array with:(el at:#CounterNameTitle) with:(el at:#CounterNameTitleIndex)].
@@ -14067,14 +13980,14 @@
 
     cachedResult := self cachedResults at:aSelector ifAbsent:nil.
     cachedResult notNil ifTrue:[
-        |currentResult|
-
-        currentResult := self perform:aSelector.
-        return := self getPerSecondViaResult1:cachedResult result2:currentResult.
-
-        self cachedResults at:aSelector put:currentResult.
+	|currentResult|
+
+	currentResult := self perform:aSelector.
+	return := self getPerSecondViaResult1:cachedResult result2:currentResult.
+
+	self cachedResults at:aSelector put:currentResult.
     ] ifFalse:[
-        self cachedResults at:aSelector put:(self perform:aSelector).
+	self cachedResults at:aSelector put:(self perform:aSelector).
     ].
 
     ^ return
@@ -14098,15 +14011,15 @@
     globalResult := Dictionary new.
 
     values2 keysDo:[:key|
-        |difference|
-
-        difference := (values2 at:key) - (values1 at:key).
-
-        runTimeInS = 0 ifTrue:[
-            globalResult at:key put:0.
-        ] ifFalse:[
-            globalResult at:key put:(difference / runTimeInS) asFloat.
-        ].
+	|difference|
+
+	difference := (values2 at:key) - (values1 at:key).
+
+	runTimeInS = 0 ifTrue:[
+	    globalResult at:key put:0.
+	] ifFalse:[
+	    globalResult at:key put:(difference / runTimeInS) asFloat.
+	].
     ].
 
     ^ globalResult
@@ -14124,15 +14037,15 @@
     globalResult := Dictionary new.
 
     values2 keysDo:[:key|
-        |difference|
-
-        difference := (values2 at:key) - (values1 at:key).
-
-        runTimeInS = 0 ifTrue:[
-            globalResult at:key put:0.
-        ] ifFalse:[
-            globalResult at:key put:(difference / runTimeInS) asFloat.
-        ].
+	|difference|
+
+	difference := (values2 at:key) - (values1 at:key).
+
+	runTimeInS = 0 ifTrue:[
+	    globalResult at:key put:0.
+	] ifFalse:[
+	    globalResult at:key put:(difference / runTimeInS) asFloat.
+	].
     ].
 
     ^ globalResult
@@ -14143,14 +14056,14 @@
 
     cachedResult := self cachedResults at:aSelector ifAbsent:nil.
     cachedResult notNil ifTrue:[
-        |currentResult|
-
-        currentResult := self perform:aSelector.
-        return := self getUsageViaResult1:cachedResult result2:currentResult.
-
-        self cachedResults at:aSelector put:currentResult.
+	|currentResult|
+
+	currentResult := self perform:aSelector.
+	return := self getUsageViaResult1:cachedResult result2:currentResult.
+
+	self cachedResults at:aSelector put:currentResult.
     ] ifFalse:[
-        self cachedResults at:aSelector put:(self perform:aSelector).
+	self cachedResults at:aSelector put:(self perform:aSelector).
     ].
 
     ^ return
@@ -14173,22 +14086,22 @@
     value2 := result2 at:#values.
 
     value1 keysDo:[:key|
-        |diff dPerSecond load1024 res|
-
-        diff := (value2 at:key) - (value1 at:key).
-        diff := diff bitShift:10.
-
-        deltaTIn100Ns = 0 ifTrue:[
-            dPerSecond := 0.
-        ] ifFalse:[
-            dPerSecond := (diff / deltaTIn100Ns) asFloat.
-        ].
-        load1024 := 1024 - dPerSecond.
-
-        res := (load1024 / 1024 * 100) asFloat.
-        res < 0 ifTrue:[res := 0].
-
-        globalResult at:key put:res.
+	|diff dPerSecond load1024 res|
+
+	diff := (value2 at:key) - (value1 at:key).
+	diff := diff bitShift:10.
+
+	deltaTIn100Ns = 0 ifTrue:[
+	    dPerSecond := 0.
+	] ifFalse:[
+	    dPerSecond := (diff / deltaTIn100Ns) asFloat.
+	].
+	load1024 := 1024 - dPerSecond.
+
+	res := (load1024 / 1024 * 100) asFloat.
+	res < 0 ifTrue:[res := 0].
+
+	globalResult at:key put:res.
     ].
 
     ^ globalResult
@@ -14204,22 +14117,22 @@
     value2 := result2 at:#values.
 
     value1 keysDo:[:key|
-        |diff dPerSecond load1024 res|
-
-        diff := (value2 at:key) - (value1 at:key).
-        diff := diff bitShift:10.
-
-        deltaTIn100Ns = 0 ifTrue:[
-            dPerSecond := 0.
-        ] ifFalse:[
-            dPerSecond := (diff / deltaTIn100Ns) asFloat.
-        ].
-        load1024 := 1024 - dPerSecond.
-
-        res := (load1024 / 1024 * 100) asFloat.
-        res < 0 ifTrue:[res := 0].
-
-        globalResult at:key put:res.
+	|diff dPerSecond load1024 res|
+
+	diff := (value2 at:key) - (value1 at:key).
+	diff := diff bitShift:10.
+
+	deltaTIn100Ns = 0 ifTrue:[
+	    dPerSecond := 0.
+	] ifFalse:[
+	    dPerSecond := (diff / deltaTIn100Ns) asFloat.
+	].
+	load1024 := 1024 - dPerSecond.
+
+	res := (load1024 / 1024 * 100) asFloat.
+	res < 0 ifTrue:[res := 0].
+
+	globalResult at:key put:res.
     ].
 
     ^ globalResult
@@ -14243,15 +14156,15 @@
     |data object counter values debugBlock numInstances|
 
     debugBlock := [:obj|
-        ^ 'obj:', obj , ' this:', self printString , ' idx:', self indexedName
+	^ 'obj:', obj , ' this:', self printString , ' idx:', self indexedName
     ].
 
     data := self dataBasic.
 
     objectIndex == 0 ifTrue:[
-        object := data objectArray at:1 ifAbsent:[debugBlock value:(object at:#ObjectNameTitle)].
+	object := data objectArray at:1 ifAbsent:[debugBlock value:(object at:#ObjectNameTitle)].
     ] ifFalse:[
-        object := data objectArray detect:[:el|(el at:#ObjectNameTitleIndex) == objectIndex] ifNone:[debugBlock value:(object at:#ObjectNameTitle)].
+	object := data objectArray detect:[:el|(el at:#ObjectNameTitleIndex) == objectIndex] ifNone:[debugBlock value:(object at:#ObjectNameTitle)].
     ].
 
     counter := (object at:#Counters) detect:[:aCounter|(aCounter at:#CounterNameTitleIndex) == counterIndex] ifNone:[debugBlock value:(object at:#ObjectNameTitle)].
@@ -14260,28 +14173,28 @@
     numInstances := object at:#NumInstances.
 
     numInstances > 0 ifTrue:[
-        1 to:numInstances do:[:idx|
-            |value instanceName|
-
-            value := (counter at:#CounterValueArray) at:idx.
-            instanceName := ((object at:#Instances) at:idx) at:#Name.
-
-            values at:instanceName put:value.
-        ].
+	1 to:numInstances do:[:idx|
+	    |value instanceName|
+
+	    value := (counter at:#CounterValueArray) at:idx.
+	    instanceName := ((object at:#Instances) at:idx) at:#Name.
+
+	    values at:instanceName put:value.
+	].
     ] ifFalse:[
-        values at:'<<singleton>>' put:(counter at:#CounterValueArray) first.
+	values at:'<<singleton>>' put:(counter at:#CounterValueArray) first.
     ].
 
     aBoolean ifTrue:[
-        |return|
-
-        return := IdentityDictionary new.
-        return at:#time put:data perfTime.
-        return at:#frequence put:data perfFreq.
-        return at:#time100nSec put:data perfTime100nSec.
-        return at:#values put:values.
-
-        ^ return
+	|return|
+
+	return := IdentityDictionary new.
+	return at:#time put:data perfTime.
+	return at:#frequence put:data perfFreq.
+	return at:#time100nSec put:data perfTime100nSec.
+	return at:#values put:values.
+
+	^ return
     ].
 
     ^ values
@@ -14303,15 +14216,15 @@
     |data object counter values debugBlock numInstances|
 
     debugBlock := [:obj|
-        ^ 'obj:', obj , ' this:', self printString , ' idx:', self indexedName
+	^ 'obj:', obj , ' this:', self printString , ' idx:', self indexedName
     ].
 
     data := self data.
 
     objectIndex == 0 ifTrue:[
-        object := data objectArray at:1 ifAbsent:[debugBlock value:(object at:#ObjectNameTitle)].
+	object := data objectArray at:1 ifAbsent:[debugBlock value:(object at:#ObjectNameTitle)].
     ] ifFalse:[
-        object := data objectArray detect:[:el|(el at:#ObjectNameTitleIndex) == objectIndex] ifNone:[debugBlock value:(object at:#ObjectNameTitle)].
+	object := data objectArray detect:[:el|(el at:#ObjectNameTitleIndex) == objectIndex] ifNone:[debugBlock value:(object at:#ObjectNameTitle)].
     ].
 
     counter := (object at:#Counters) detect:[:aCounter|(aCounter at:#CounterNameTitleIndex) == counterIndex] ifNone:[debugBlock value:(object at:#ObjectNameTitle)].
@@ -14320,28 +14233,28 @@
     numInstances := object at:#NumInstances.
 
     numInstances > 0 ifTrue:[
-        1 to:numInstances do:[:idx|
-            |value instanceName|
-
-            value := (counter at:#CounterValueArray) at:idx.
-            instanceName := ((object at:#Instances) at:idx) at:#Name.
-
-            values at:instanceName put:value.
-        ].
+	1 to:numInstances do:[:idx|
+	    |value instanceName|
+
+	    value := (counter at:#CounterValueArray) at:idx.
+	    instanceName := ((object at:#Instances) at:idx) at:#Name.
+
+	    values at:instanceName put:value.
+	].
     ] ifFalse:[
-        values at:'<<singleton>>' put:(counter at:#CounterValueArray) first.
+	values at:'<<singleton>>' put:(counter at:#CounterValueArray) first.
     ].
 
     aBoolean ifTrue:[
-        |return|
-
-        return := IdentityDictionary new.
-        return at:#time put:data perfTime.
-        return at:#frequence put:data perfFreq.
-        return at:#time100nSec put:data perfTime100nSec.
-        return at:#values put:values.
-
-        ^ return
+	|return|
+
+	return := IdentityDictionary new.
+	return at:#time put:data perfTime.
+	return at:#frequence put:data perfFreq.
+	return at:#time100nSec put:data perfTime100nSec.
+	return at:#values put:values.
+
+	^ return
     ].
 
     ^ values
@@ -14352,7 +14265,7 @@
 current
 
     TheOneAndOnlyInstance isNil ifTrue:[
-        TheOneAndOnlyInstance := self new.
+	TheOneAndOnlyInstance := self new.
     ].
 
     ^ TheOneAndOnlyInstance
@@ -14374,7 +14287,7 @@
     ^ self getValuesByCounter:218 timed:true
 
     "
-        self current diskBytes
+	self current diskBytes
     "
 !
 
@@ -14382,7 +14295,7 @@
     ^ self getBasicValuesByCounter:218 timed:true
 
     "
-        self current diskBytesBasic
+	self current diskBytesBasic
     "
 !
 
@@ -14390,7 +14303,7 @@
     ^ self getPerSecondViaPerformBlock:[self diskBytes]
 
     "
-        self current diskBytesPerSecond
+	self current diskBytesPerSecond
     "
 !
 
@@ -14398,7 +14311,7 @@
     ^ self getPerSecondFromLast:#diskBytesBasic
 
     "
-        self current diskBytesPerSecondFromLast
+	self current diskBytesPerSecondFromLast
     "
 !
 
@@ -14406,7 +14319,7 @@
     ^ self getValuesByCounter:198
 
     "
-        self current diskQueueLength
+	self current diskQueueLength
     "
 !
 
@@ -14414,7 +14327,7 @@
     ^ self getValuesByCounter:214 timed:true
 
     "
-        self current diskRead
+	self current diskRead
     "
 !
 
@@ -14422,7 +14335,7 @@
     ^ self getBasicValuesByCounter:214 timed:true
 
     "
-        self current diskReadBasic
+	self current diskReadBasic
     "
 !
 
@@ -14430,7 +14343,7 @@
     ^ self getPerSecondViaPerformBlock:[self diskRead]
 
     "
-        self current diskReadsPerSecond
+	self current diskReadsPerSecond
     "
 !
 
@@ -14438,7 +14351,7 @@
     ^ self getPerSecondFromLast:#diskReadBasic
 
     "
-        self current diskReadsPerSecondFromLast
+	self current diskReadsPerSecondFromLast
     "
 !
 
@@ -14446,7 +14359,7 @@
     ^ self getValuesByCounter:408
 
     "
-        self current diskSpaceFreeInMegaByte
+	self current diskSpaceFreeInMegaByte
     "
 !
 
@@ -14454,7 +14367,7 @@
     ^ self getValuesByCounter:212 timed:true
 
     "
-        self current diskTransfers
+	self current diskTransfers
     "
 !
 
@@ -14462,7 +14375,7 @@
     ^ self getBasicValuesByCounter:212 timed:true
 
     "
-        self current diskTransfersBasic
+	self current diskTransfersBasic
     "
 !
 
@@ -14470,7 +14383,7 @@
     ^ self getPerSecondViaPerformBlock:[self diskTransfers]
 
     "
-        self current diskTransfersPerSecond
+	self current diskTransfersPerSecond
     "
 !
 
@@ -14478,7 +14391,7 @@
     ^ self getPerSecondFromLast:#diskTransfersBasic
 
     "
-        self current diskTransfersPerSecondFromlast
+	self current diskTransfersPerSecondFromlast
     "
 !
 
@@ -14486,7 +14399,7 @@
     ^ self getValuesByCounter:216 timed:true
 
     "
-        self current diskWrite
+	self current diskWrite
     "
 !
 
@@ -14494,7 +14407,7 @@
     ^ self getBasicValuesByCounter:216 timed:true
 
     "
-        self current diskWriteBasic
+	self current diskWriteBasic
     "
 !
 
@@ -14502,7 +14415,7 @@
     ^ self getPerSecondViaPerformBlock:[self diskWrite]
 
     "
-        self current diskWritesPerSecond
+	self current diskWritesPerSecond
     "
 !
 
@@ -14510,7 +14423,7 @@
     ^ self getPerSecondFromLast:#diskWriteBasic
 
     "
-        self current diskWritesPerSecondFromLast
+	self current diskWritesPerSecondFromLast
     "
 ! !
 
@@ -14519,7 +14432,7 @@
 current
 
     TheOneAndOnlyInstance isNil ifTrue:[
-        TheOneAndOnlyInstance := self new.
+	TheOneAndOnlyInstance := self new.
     ].
 
     ^ TheOneAndOnlyInstance
@@ -14548,12 +14461,12 @@
     indexNameArray := OrderedCollection new.
 
     data objectArray do:[:anObject|
-        |index name|
-
-        index := anObject at:#ObjectNameTitleIndex.
-        name := Win32OperatingSystem::PerformanceData counterIndexTextDictionary at:index.
-
-        indexNameArray add:(Array with:name with:index).
+	|index name|
+
+	index := anObject at:#ObjectNameTitleIndex.
+	name := Win32OperatingSystem::PerformanceData counterIndexTextDictionary at:index.
+
+	indexNameArray add:(Array with:name with:index).
     ].
 
     ^ indexNameArray
@@ -14564,7 +14477,7 @@
 current
 
     TheOneAndOnlyInstance isNil ifTrue:[
-        TheOneAndOnlyInstance := self new.
+	TheOneAndOnlyInstance := self new.
     ].
 
     ^ TheOneAndOnlyInstance
@@ -14586,7 +14499,7 @@
     ^ self getValuesByCounter:1380
 
     "
-        self current availableKBytes
+	self current availableKBytes
     "
 !
 
@@ -14594,7 +14507,7 @@
     ^ self getValuesByCounter:1382
 
     "
-        self current availableMBytes
+	self current availableMBytes
     "
 ! !
 
@@ -14603,7 +14516,7 @@
 current
 
     TheOneAndOnlyInstance isNil ifTrue:[
-        TheOneAndOnlyInstance := self new.
+	TheOneAndOnlyInstance := self new.
     ].
 
     ^ TheOneAndOnlyInstance
@@ -14629,7 +14542,7 @@
     ^ self getValuesByCounter:264 timed:true
 
     "
-        self current bytesReceived
+	self current bytesReceived
     "
 !
 
@@ -14637,7 +14550,7 @@
     ^ self getBasicValuesByCounter:264 timed:true
 
     "
-        self current bytesReceivedBasic
+	self current bytesReceivedBasic
     "
 !
 
@@ -14645,7 +14558,7 @@
     ^ self getPerSecondViaPerformBlock:[self bytesReceived]
 
     "
-        self current bytesReceivedPerSecond
+	self current bytesReceivedPerSecond
     "
 !
 
@@ -14653,7 +14566,7 @@
     ^ self getPerSecondFromLast:#bytesReceivedBasic
 
     "
-        self current bytesReceivedPerSecondFromlast
+	self current bytesReceivedPerSecondFromlast
     "
 !
 
@@ -14661,7 +14574,7 @@
     ^ self getValuesByCounter:506 timed:true
 
     "
-        self current bytesSent
+	self current bytesSent
     "
 !
 
@@ -14669,7 +14582,7 @@
     ^ self getBasicValuesByCounter:506 timed:true
 
     "
-        self current bytesSentBasic
+	self current bytesSentBasic
     "
 !
 
@@ -14677,7 +14590,7 @@
     ^ self getPerSecondViaPerformBlock:[self bytesSent]
 
     "
-        self current bytesSentPerSecond
+	self current bytesSentPerSecond
     "
 !
 
@@ -14685,7 +14598,7 @@
     ^ self getPerSecondFromLast:#bytesSentBasic
 
     "
-        self current bytesSentPerSecondFromlast
+	self current bytesSentPerSecondFromlast
     "
 !
 
@@ -14695,13 +14608,13 @@
     modifiedDictionary := Dictionary new.
 
     (self getPerSecondViaPerformBlock:[self bytesReceived]) keysAndValuesDo:[:key :value|
-        modifiedDictionary at:key put:(value / 1024).
+	modifiedDictionary at:key put:(value / 1024).
     ].
 
     ^ modifiedDictionary
 
     "
-        self current kBytesReceivedPerSecond
+	self current kBytesReceivedPerSecond
     "
 !
 
@@ -14714,13 +14627,13 @@
     modifiedDictionary := Dictionary new.
 
     return keysAndValuesDo:[:key :value|
-        modifiedDictionary at:key put:(value / 1024).
+	modifiedDictionary at:key put:(value / 1024).
     ].
 
     ^ modifiedDictionary
 
     "
-        self current kBytesReceivedPerSecondFromLast
+	self current kBytesReceivedPerSecondFromLast
     "
 !
 
@@ -14730,13 +14643,13 @@
     modifiedDictionary := Dictionary new.
 
     (self getPerSecondViaPerformBlock:[self bytesSent]) keysAndValuesDo:[:key :value|
-        modifiedDictionary at:key put:(value / 1024).
+	modifiedDictionary at:key put:(value / 1024).
     ].
 
     ^ modifiedDictionary
 
     "
-        self current kBytesSentPerSecond
+	self current kBytesSentPerSecond
     "
 !
 
@@ -14749,13 +14662,13 @@
     modifiedDictionary := Dictionary new.
 
     return keysAndValuesDo:[:key :value|
-        modifiedDictionary at:key put:(value / 1024).
+	modifiedDictionary at:key put:(value / 1024).
     ].
 
     ^ modifiedDictionary
 
     "
-        self current kBytesSentPerSecondFromLast
+	self current kBytesSentPerSecondFromLast
     "
 ! !
 
@@ -14764,7 +14677,7 @@
 current
 
     TheOneAndOnlyInstance isNil ifTrue:[
-        TheOneAndOnlyInstance := self new.
+	TheOneAndOnlyInstance := self new.
     ].
 
     ^ TheOneAndOnlyInstance
@@ -14786,7 +14699,7 @@
     ^ self getValuesByCounter:6 timed:true
 
     "
-        self current processTime
+	self current processTime
     "
 !
 
@@ -14794,7 +14707,7 @@
     ^ self getBasicValuesByCounter:6 timed:true
 
     "
-        self current processTimeBasic
+	self current processTimeBasic
     "
 !
 
@@ -14804,13 +14717,13 @@
     modifiedDictionary := Dictionary new.
 
     (self getUsageViaPerformBlock:[self processTime]) keysAndValuesDo:[:key :value|
-        modifiedDictionary at:key put:(100 - value).
+	modifiedDictionary at:key put:(100 - value).
     ].
 
     ^ modifiedDictionary
 
     "
-        self current processUsage
+	self current processUsage
     "
 !
 
@@ -14823,13 +14736,13 @@
     modifiedDictionary := Dictionary new.
 
     return keysAndValuesDo:[:key :value|
-        modifiedDictionary at:key put:(100 - value).
+	modifiedDictionary at:key put:(100 - value).
     ].
 
     ^ modifiedDictionary
 
     "
-        self current processUsageFromLast
+	self current processUsageFromLast
     "
 !
 
@@ -14838,7 +14751,7 @@
     ^ (self data objectArray first at:#Instances) collect:[:el|el at:#Name]
 
     "
-        self current runningProcessNameList
+	self current runningProcessNameList
     "
 !
 
@@ -14847,7 +14760,7 @@
     ^ (self data objectArray first at:#NumInstances)
 
     "
-        self current runningProcesses
+	self current runningProcesses
     "
 ! !
 
@@ -14856,7 +14769,7 @@
 current
 
     TheOneAndOnlyInstance isNil ifTrue:[
-        TheOneAndOnlyInstance := self new.
+	TheOneAndOnlyInstance := self new.
     ].
 
     ^ TheOneAndOnlyInstance
@@ -14878,7 +14791,7 @@
     ^ self getValuesByCounter:148 timed:true
 
     "
-        self current interrupts
+	self current interrupts
     "
 !
 
@@ -14886,7 +14799,7 @@
     ^ self getBasicValuesByCounter:148 timed:true
 
     "
-        self current interruptsBasic
+	self current interruptsBasic
     "
 !
 
@@ -14894,7 +14807,7 @@
     ^ self getPerSecondViaPerformBlock:[self interrupts]
 
     "
-        self current interruptsPerSecond
+	self current interruptsPerSecond
     "
 !
 
@@ -14902,7 +14815,7 @@
     ^ self getPerSecondFromLast:#interruptsBasic
 
     "
-        self current interruptsPerSecondFromLast
+	self current interruptsPerSecondFromLast
     "
 !
 
@@ -14910,7 +14823,7 @@
     ^ self getValuesByCounter:6 timed:true
 
     "
-        self current processorTime
+	self current processorTime
     "
 !
 
@@ -14918,7 +14831,7 @@
     ^ self getBasicValuesByCounter:6 timed:true
 
     "
-        self current processorTimeBasic
+	self current processorTimeBasic
     "
 !
 
@@ -14926,7 +14839,7 @@
     ^ self getUsageViaPerformBlock:[self processorTime]
 
     "
-        self current processorUsage
+	self current processorUsage
     "
 !
 
@@ -14934,7 +14847,7 @@
     ^ self getUsageFromLast:#processorTimeBasic
 
     "
-        self current processorUsageFromLast
+	self current processorUsageFromLast
     "
 ! !
 
@@ -14945,10 +14858,10 @@
     |defaultPriority|
 
     Error handle:[:ex |
-        Transcript showCR: 'PrinterInfo2 error getting defaultPriority - ', ex description.
-        defaultPriority := 0.
+	Transcript showCR: 'PrinterInfo2 error getting defaultPriority - ', ex description.
+	defaultPriority := 0.
     ] do:[
-        defaultPriority := self unsignedLongAt:(60 + 1)
+	defaultPriority := self unsignedLongAt:(60 + 1)
     ].
     ^ defaultPriority
 
@@ -14960,15 +14873,15 @@
     |pComment|
 
     Error handle:[:ex |
-        Transcript showCR: 'PrinterInfo2 error getting pComment - ', ex description.
-        pComment := 0.
+	Transcript showCR: 'PrinterInfo2 error getting pComment - ', ex description.
+	pComment := 0.
     ] do:[
-        pComment := self unsignedLongAt:(20 + 1).
+	pComment := self unsignedLongAt:(20 + 1).
     ].
 
     ^ pComment == 0
-        ifTrue:''
-        ifFalse:[ (ExternalBytes address:pComment) stringAt:1 ]
+	ifTrue:''
+	ifFalse:[ (ExternalBytes address:pComment) stringAt:1 ]
 
     "Created: / 01-08-2006 / 14:02:55 / fm"
     "Modified: / 16-04-2007 / 13:08:39 / cg"
@@ -14978,10 +14891,10 @@
     |pName|
 
     Error handle:[:ex |
-        Transcript showCR: 'PrinterInfo2 error getting pDriverName - ', ex description.
-        pName := 0.
+	Transcript showCR: 'PrinterInfo2 error getting pDriverName - ', ex description.
+	pName := 0.
     ] do:[
-        pName := self unsignedLongAt:(16 + 1).
+	pName := self unsignedLongAt:(16 + 1).
     ].
     pName == 0 ifTrue:[^ ''].
     ^ (ExternalBytes address:pName) stringAt:1
@@ -14994,18 +14907,18 @@
     |pLocation externalBytes|
 
     Error handle:[:ex |
-        Transcript showCR: 'PrinterInfo2 error getting pLocation - ', ex description.
-        pLocation := 0.
+	Transcript showCR: 'PrinterInfo2 error getting pLocation - ', ex description.
+	pLocation := 0.
     ] do:[
-        pLocation := self unsignedLongAt:(24 + 1).
+	pLocation := self unsignedLongAt:(24 + 1).
     ].
 
     pLocation == 0 ifTrue:[^ nil].
 
     externalBytes := ExternalBytes address:pLocation.
     ^ externalBytes isEmpty
-        ifTrue:[ nil ]
-        ifFalse:[ externalBytes stringAt:1 ]
+	ifTrue:[ nil ]
+	ifFalse:[ externalBytes stringAt:1 ]
 
     "Created: / 01-08-2006 / 14:03:21 / fm"
     "Modified: / 18-10-2006 / 12:06:45 / User"
@@ -15017,10 +14930,10 @@
     |priority|
 
     Error handle:[:ex |
-        Transcript showCR: 'PrinterInfo2 error getting priority - ', ex description.
-        priority := 0.
+	Transcript showCR: 'PrinterInfo2 error getting priority - ', ex description.
+	priority := 0.
     ] do:[
-        priority := self unsignedLongAt: 56 + 1
+	priority := self unsignedLongAt: 56 + 1
     ].
     ^ priority
 
@@ -15033,10 +14946,10 @@
     |status|
 
     Error handle:[:ex |
-        Transcript showCR: 'PrinterInfo2 error getting status - ', ex description.
-        status := -1.
+	Transcript showCR: 'PrinterInfo2 error getting status - ', ex description.
+	status := -1.
     ] do:[
-        status := self unsignedLongAt: 72 + 1
+	status := self unsignedLongAt: 72 + 1
     ].
     ^ status
 
@@ -15050,13 +14963,13 @@
     "returns a collection of root keyNames"
 
     ^ #(
-        'HKEY_CLASSES_ROOT'
-        'HKEY_CURRENT_USER'
-        'HKEY_LOCAL_MACHINE'
-        'HKEY_USERS'
-        'HKEY_PERFORMANCE_DATA'
-        'HKEY_CURRENT_CONFIG'
-        'HKEY_DYN_DATA'
+	'HKEY_CLASSES_ROOT'
+	'HKEY_CURRENT_USER'
+	'HKEY_LOCAL_MACHINE'
+	'HKEY_USERS'
+	'HKEY_PERFORMANCE_DATA'
+	'HKEY_CURRENT_CONFIG'
+	'HKEY_DYN_DATA'
       )
 !
 
@@ -15073,184 +14986,184 @@
     Interface to a WIN32 registry.
 
     As this is a private class, access it via
-        Win32OperatingSystem registryEntry
+	Win32OperatingSystem registryEntry
 
     [author:]
-        Claus Gittinger (initial version & cleanup)
+	Claus Gittinger (initial version & cleanup)
 "
 !
 
 examples
 "
     retrieve an existing entry by key:
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X'
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X'
+									[exEnd]
 
 
     retrieve a non-existing entry by key:
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\xxx'
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\xxx'
+									[exEnd]
 
 
     ask a keys value:
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\Microsoft\Windows\CurrentVersion'.
-        Transcript show:'Windows serial NR:'; showCR:(k valueNamed:'ProductId').
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X'.
-        Transcript showCR:(k valueNamed:'CurrentVersion').
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\Microsoft\Windows\CurrentVersion'.
+	Transcript show:'Windows serial NR:'; showCR:(k valueNamed:'ProductId').
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X'.
+	Transcript showCR:(k valueNamed:'CurrentVersion').
+									[exEnd]
 
 
     create a sub-key (if not already present):
-                                                                        [exBegin]
-        |k subKey|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X'.
-        subKey := k createSubKeyNamed:'RegistryDemo'
-                                                                        [exEnd]
+									[exBegin]
+	|k subKey|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X'.
+	subKey := k createSubKeyNamed:'RegistryDemo'
+									[exEnd]
 
 
     change a keys value:
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X\RegistryDemo'.
-        k valueNamed:'FooBarBaz' put:'a foo bar baz string'.
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X\RegistryDemo'.
+	k valueNamed:'FooBarBaz' put:'a foo bar baz string'.
+									[exEnd]
 
     delete a value:
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X\RegistryDemo'.
-        k deleteValueNamed:'FooBarBaz'.
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X\RegistryDemo'.
+	k deleteValueNamed:'FooBarBaz'.
+									[exEnd]
 
     delete a key:
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X'.
-        k deleteSubKeyNamed:'RegistryDemo'.
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software\eXept\Smalltalk/X'.
+	k deleteSubKeyNamed:'RegistryDemo'.
+									[exEnd]
 
     enumerate keys:
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software'.
-        k subKeysDo:[:subKey |
-            Transcript showCR:subKey path
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software'.
+	k subKeysDo:[:subKey |
+	    Transcript showCR:subKey path
+	]
+									[exEnd]
 
     enumerate all keys (recursive):
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software'.
-        k allSubKeysDo:[:subKey |
-            Transcript showCR:subKey path
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\Software'.
+	k allSubKeysDo:[:subKey |
+	    Transcript showCR:subKey path
+	]
+									[exEnd]
 
     fetch value by index:
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X'.
-        Transcript showCR:(k valueNameAtIndex:0)
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X'.
+	Transcript showCR:(k valueNameAtIndex:0)
+									[exEnd]
 
 
     enumerate value names:
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X'.
-        k valueNamesDo:[:nm  |
-           Transcript showCR:nm.
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X'.
+	k valueNamesDo:[:nm  |
+	   Transcript showCR:nm.
+	]
+									[exEnd]
 
     enumerate values:
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X'.
-        k valueNamesAndValuesDo:[:nm :val |
-            Transcript showCR:(nm , ' -> ' , val storeString).
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X'.
+	k valueNamesAndValuesDo:[:nm :val |
+	    Transcript showCR:(nm , ' -> ' , val storeString).
+	]
+									[exEnd]
 
     search for a value (where does NT store the domain ?):
-                                                                        [exBegin]
-        |k|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\System'.
-        k subKeysDo:[:subKey |
-            subKey subKeysDo:[:subSubKey |
-                |tcp params|
-
-                (subSubKey path asLowercase endsWith:'services') ifTrue:[
-                    tcp := subSubKey subKeyNamed:'tcpip'.
-                    tcp notNil ifTrue:[
-                        params := tcp subKeyNamed:'parameters'.
-                        params notNil ifTrue:[
-                            Transcript showCR:'Domain is found in ' , params path ,
-                                        ' value: ' , (params valueNamed:'Domain').
-                            params close.
-                        ].
-                        tcp close.
-                    ]
-                ]
-            ]
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|k|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_LOCAL_MACHINE\System'.
+	k subKeysDo:[:subKey |
+	    subKey subKeysDo:[:subSubKey |
+		|tcp params|
+
+		(subSubKey path asLowercase endsWith:'services') ifTrue:[
+		    tcp := subSubKey subKeyNamed:'tcpip'.
+		    tcp notNil ifTrue:[
+			params := tcp subKeyNamed:'parameters'.
+			params notNil ifTrue:[
+			    Transcript showCR:'Domain is found in ' , params path ,
+					' value: ' , (params valueNamed:'Domain').
+			    params close.
+			].
+			tcp close.
+		    ]
+		]
+	    ]
+	]
+									[exEnd]
     register an exe for shell-open:
-                                                                        [exBegin]
-        |k stx shell open cmd st_af edit st owl list id|
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_CURRENT_USER\Software\Classes\Applications'.
-        stx := k createSubKeyNamed:'SmalltalkX.exe'.
-        shell := stx createSubKeyNamed:'shell'.
-        open := shell createSubKeyNamed:'open'.
-        cmd := open createSubKeyNamed:'command'.
-        cmd defaultValue:(Character doubleQuote asString,OperatingSystem nameOfSTXExecutable,Character doubleQuote,
-                         ' ',Character doubleQuote,'%1',Character doubleQuote).
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_CURRENT_USER\Software\Classes'.
-        st_af := k createSubKeyNamed:'st_auto_file'.
-        shell := st_af createSubKeyNamed:'shell'.
-        open := shell createSubKeyNamed:'open'.
-        cmd := open createSubKeyNamed:'command'.
-        cmd defaultValue:(Character doubleQuote asString,OperatingSystem nameOfSTXExecutable,Character doubleQuote,
-                         ' --open ',Character doubleQuote,'%1',Character doubleQuote).
-        edit := shell createSubKeyNamed:'edit'.
-        cmd := edit createSubKeyNamed:'command'.
-        cmd defaultValue:(Character doubleQuote asString,OperatingSystem nameOfSTXExecutable,Character doubleQuote,
-                         ' --edit ',Character doubleQuote,'%1',Character doubleQuote).
-
-        k := Win32OperatingSystem registryEntry key:'HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Explorer\FileExts'.
-        st := k createSubKeyNamed:'.st'.
-        owl := st createSubKeyNamed:'OpenWithList'.
-        list := owl valueNames.
-        (list contains:[:k | (owl valueNamed:k) = 'SmalltalkX.exe']) ifTrue:[
-            Transcript showCR:'already registered.'.
-        ] ifFalse:[
-            id := ($a to:$z) detect:[:k | (list includes:(k asString)) not] ifNone:nil.
-            owl valueNamed:id asString put:'SmalltalkX.exe'.
-        ]
-                                                                        [exEnd]
+									[exBegin]
+	|k stx shell open cmd st_af edit st owl list id|
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_CURRENT_USER\Software\Classes\Applications'.
+	stx := k createSubKeyNamed:'SmalltalkX.exe'.
+	shell := stx createSubKeyNamed:'shell'.
+	open := shell createSubKeyNamed:'open'.
+	cmd := open createSubKeyNamed:'command'.
+	cmd defaultValue:(Character doubleQuote asString,OperatingSystem nameOfSTXExecutable,Character doubleQuote,
+			 ' ',Character doubleQuote,'%1',Character doubleQuote).
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_CURRENT_USER\Software\Classes'.
+	st_af := k createSubKeyNamed:'st_auto_file'.
+	shell := st_af createSubKeyNamed:'shell'.
+	open := shell createSubKeyNamed:'open'.
+	cmd := open createSubKeyNamed:'command'.
+	cmd defaultValue:(Character doubleQuote asString,OperatingSystem nameOfSTXExecutable,Character doubleQuote,
+			 ' --open ',Character doubleQuote,'%1',Character doubleQuote).
+	edit := shell createSubKeyNamed:'edit'.
+	cmd := edit createSubKeyNamed:'command'.
+	cmd defaultValue:(Character doubleQuote asString,OperatingSystem nameOfSTXExecutable,Character doubleQuote,
+			 ' --edit ',Character doubleQuote,'%1',Character doubleQuote).
+
+	k := Win32OperatingSystem registryEntry key:'HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Explorer\FileExts'.
+	st := k createSubKeyNamed:'.st'.
+	owl := st createSubKeyNamed:'OpenWithList'.
+	list := owl valueNames.
+	(list contains:[:k | (owl valueNamed:k) = 'SmalltalkX.exe']) ifTrue:[
+	    Transcript showCR:'already registered.'.
+	] ifFalse:[
+	    id := ($a to:$z) detect:[:k | (list includes:(k asString)) not] ifNone:nil.
+	    owl valueNamed:id asString put:'SmalltalkX.exe'.
+	]
+									[exEnd]
 
 
 
@@ -15300,31 +15213,31 @@
     HKEY_CLASSES_ROOT isNil ifTrue:[self initialize].
 
     specialKeyStringOrSymbol = #'HKEY_CLASSES_ROOT' ifTrue:[
-        ^ HKEY_CLASSES_ROOT.
+	^ HKEY_CLASSES_ROOT.
     ].
     specialKeyStringOrSymbol = #'HKEY_CURRENT_USER' ifTrue:[
-        ^ HKEY_CURRENT_USER.
+	^ HKEY_CURRENT_USER.
     ].
     specialKeyStringOrSymbol = #'HKEY_LOCAL_MACHINE' ifTrue:[
-        ^ HKEY_LOCAL_MACHINE.
+	^ HKEY_LOCAL_MACHINE.
     ].
     specialKeyStringOrSymbol = #'HKEY_USERS' ifTrue:[
-        ^ HKEY_USERS.
+	^ HKEY_USERS.
     ].
     specialKeyStringOrSymbol = #'HKEY_PERFORMANCE_DATA' ifTrue:[
-        ^ HKEY_PERFORMANCE_DATA.
+	^ HKEY_PERFORMANCE_DATA.
     ].
     specialKeyStringOrSymbol = #'HKEY_CURRENT_CONFIG' ifTrue:[
-        ^ HKEY_CURRENT_CONFIG.
+	^ HKEY_CURRENT_CONFIG.
     ].
     specialKeyStringOrSymbol = #'HKEY_DYN_DATA' ifTrue:[
-        ^ HKEY_DYN_DATA.
+	^ HKEY_DYN_DATA.
     ].
     specialKeyStringOrSymbol = #'HKEY_PERFORMANCE_TEXT' ifTrue:[
-        ^ HKEY_PERFORMANCE_TEXT.
+	^ HKEY_PERFORMANCE_TEXT.
     ].
     specialKeyStringOrSymbol = #'HKEY_PERFORMANCE_NLSTEXT' ifTrue:[
-        ^ HKEY_PERFORMANCE_NLSTEXT.
+	^ HKEY_PERFORMANCE_NLSTEXT.
     ].
 
     ^ nil
@@ -15337,7 +15250,7 @@
     "handle image restarts and refetch registry handles"
 
     (something == #returnFromSnapshot) ifTrue:[
-        self initialize
+	self initialize
     ]
 
     "Created: 15.6.1996 / 15:14:03 / cg"
@@ -15350,9 +15263,9 @@
     |h newEntry|
 
     aHandleValue isInteger ifTrue:[
-        h := ExternalAddress newAddress:aHandleValue
+	h := ExternalAddress newAddress:aHandleValue
     ] ifFalse:[
-        h := aHandleValue
+	h := aHandleValue
     ].
 
     "/ rootKeys are not registered for RegClose ...
@@ -15400,9 +15313,9 @@
 key:aKeyNamePath flags:flags
     "retrieve an entry by full path name (starting at a root).
      flags may be one of:
-        #KEY_WOW64_64KEY to force access to the 64Bit Windows key,
-        #KEY_WOW64_32KEY to force access to the 32Bit Windows key,
-        or nil, to access the key (32/64) for the current application"
+	#KEY_WOW64_64KEY to force access to the 64Bit Windows key,
+	#KEY_WOW64_32KEY to force access to the 32Bit Windows key,
+	or nil, to access the key (32/64) for the current application"
 
     ^ self key:aKeyNamePath flags:flags createIfAbsent:false
 
@@ -15421,9 +15334,9 @@
 key:aKeyNamePath flags:flags createIfAbsent:createIfAbsent
     "retrieve an entry by full path name (starting at a root).
      flags may be one of:
-        #KEY_WOW64_64KEY to force access to the 64Bit Windows key,
-        #KEY_WOW64_32KEY to force access to the 32Bit Windows key,
-        or nil, to access the key (32/64) for the current application"
+	#KEY_WOW64_64KEY to force access to the 64Bit Windows key,
+	#KEY_WOW64_32KEY to force access to the 32Bit Windows key,
+	or nil, to access the key (32/64) for the current application"
 
     |idx first rest root|
 
@@ -15431,11 +15344,11 @@
 
     idx := aKeyNamePath indexOf:(self separator).
     idx == 0 ifTrue:[
-        first := aKeyNamePath.
-        rest := nil.
+	first := aKeyNamePath.
+	rest := nil.
     ] ifFalse:[
-        first := aKeyNamePath copyTo:idx-1.
-        rest := aKeyNamePath copyFrom:idx+1
+	first := aKeyNamePath copyTo:idx-1.
+	rest := aKeyNamePath copyFrom:idx+1
     ].
 
     first := first asUppercase.
@@ -15443,17 +15356,17 @@
     "/ the first is a pseudo name
     root := self rootKey:first.
     root isNil ifTrue:[
-        ^ nil
+	^ nil
     ].
 
     rest size == 0 ifTrue:[
-        ^ root
+	^ root
     ].
 
     Error handle:[:ex |
-        ^ nil
+	^ nil
     ] do:[
-        ^ root subKeyNamed:rest flags:flags createIfAbsent:createIfAbsent.
+	^ root subKeyNamed:rest flags:flags createIfAbsent:createIfAbsent.
     ].
 
     "
@@ -15590,7 +15503,7 @@
 
     k := self key:'HKEY_CLASSES_ROOT\MIME\Database\Content Type\',mimeType.
     k notNil ifTrue:[
-        suffix := k valueNamed:'extension'.
+	suffix := k valueNamed:'extension'.
     ].
     ^ suffix
 !
@@ -15604,35 +15517,35 @@
     suffix isNil ifTrue:[^ nil].
 
     (suffix startsWith:'.') ifTrue:[
-        suffix := suffix copyFrom:2
+	suffix := suffix copyFrom:2
     ].
     k := self key:'HKEY_CLASSES_ROOT\.',suffix.
 
     k notNil ifTrue:[
-        fkey := (k valueNamed:'').
+	fkey := (k valueNamed:'').
     ].
     fkey isNil ifTrue:[
-        fkey := suffix,'_auto_file'
+	fkey := suffix,'_auto_file'
     ].
 
     fkey notEmptyOrNil ifTrue:[
 
-        redirect := nil.
-
-        k := Win32OperatingSystem::RegistryEntry key:('HKEY_CLASSES_ROOT\' , fkey , '\CurVer').
-        k notNil ifTrue:[
-            redirect := k defaultValue
-        ].
-
-        redirect isNil ifTrue:[
-             k := Win32OperatingSystem::RegistryEntry key:('HKEY_CLASSES_ROOT\' , (fkey) , '\shell\',operation,'\command').
-        ] ifFalse:[
-             k := Win32OperatingSystem::RegistryEntry key:('HKEY_CLASSES_ROOT\' , (redirect) , '\shell\',operation,'\command').
-        ].
-
-        k notNil ifTrue:[
-            cmd := k defaultValue
-        ].
+	redirect := nil.
+
+	k := Win32OperatingSystem::RegistryEntry key:('HKEY_CLASSES_ROOT\' , fkey , '\CurVer').
+	k notNil ifTrue:[
+	    redirect := k defaultValue
+	].
+
+	redirect isNil ifTrue:[
+	     k := Win32OperatingSystem::RegistryEntry key:('HKEY_CLASSES_ROOT\' , (fkey) , '\shell\',operation,'\command').
+	] ifFalse:[
+	     k := Win32OperatingSystem::RegistryEntry key:('HKEY_CLASSES_ROOT\' , (redirect) , '\shell\',operation,'\command').
+	].
+
+	k notNil ifTrue:[
+	    cmd := k defaultValue
+	].
     ].
 
 
@@ -15657,8 +15570,8 @@
 
     "
      self
-        stringValueFor:'Content Type'
-        atKey:'HKEY_CLASSES_ROOT\.au'
+	stringValueFor:'Content Type'
+	atKey:'HKEY_CLASSES_ROOT\.au'
     "
 ! !
 
@@ -15713,9 +15626,9 @@
      If it already exists, return it.
      Return nil if the new key cannot be created.
      flags may be one of:
-        #KEY_WOW64_64KEY to force access to the 64Bit Windows key,
-        #KEY_WOW64_32KEY to force access to the 32Bit Windows key,
-        or nil, to access the key (32/64) for the current application"
+	#KEY_WOW64_64KEY to force access to the 64Bit Windows key,
+	#KEY_WOW64_32KEY to force access to the 32Bit Windows key,
+	or nil, to access the key (32/64) for the current application"
 
 
     ^ self subKeyNamed:subKeyString flags:flags createIfAbsent:true
@@ -15747,12 +15660,12 @@
     "delete a key below mySelf.
      Return true on success.
      flags may be one of:
-        #KEY_WOW64_64KEY to force access to the 64Bit Windows key,
-        #KEY_WOW64_32KEY to force access to the 32Bit Windows key,
-        or nil, to access the key (32/64) for the current application.
+	#KEY_WOW64_64KEY to force access to the 64Bit Windows key,
+	#KEY_WOW64_32KEY to force access to the 32Bit Windows key,
+	or nil, to access the key (32/64) for the current application.
 
      CAVEAT: due to a missing library entry in the BCC system,
-             the flags are currently ignored"
+	     the flags are currently ignored"
 
     |subKeyStringZ errorNumber|
 
@@ -15770,40 +15683,40 @@
     int _flags = 0;
 
     if (flags != nil) {
-        if (flags == @symbol(KEY_WOW64_64KEY)) {
-            _flags = KEY_WOW64_64KEY;
-        } else if (flags == @symbol(KEY_WOW64_32KEY)) {
-            _flags = KEY_WOW64_32KEY;
-        } else {
-            errorNumber = @symbol(badArgument2);
-            goto out;
-        }
+	if (flags == @symbol(KEY_WOW64_64KEY)) {
+	    _flags = KEY_WOW64_64KEY;
+	} else if (flags == @symbol(KEY_WOW64_32KEY)) {
+	    _flags = KEY_WOW64_32KEY;
+	} else {
+	    errorNumber = @symbol(badArgument2);
+	    goto out;
+	}
     }
 
     if (__isExternalAddressLike(__INST(handle))
      && __isUnicode16String(subKeyStringZ)) {
-        myKey = (HKEY)__externalAddressVal(__INST(handle));
+	myKey = (HKEY)__externalAddressVal(__INST(handle));
 #ifdef __BORLANDC__
-        _retVal = RegDeleteKeyW(myKey, __unicode16StringVal(subKeyStringZ));
-#else
-        _retVal = RegDeleteKeyExW(myKey,
-                    __unicode16StringVal(subKeyStringZ),
-                    _flags,
-                    0); // reserved
-#endif
-        if (_retVal == ERROR_SUCCESS) {
-            RETURN (true);
-        }
-        if ((_retVal != ERROR_PATH_NOT_FOUND)
-         && (_retVal != ERROR_FILE_NOT_FOUND)) {
-            errorNumber = __MKSMALLINT(_retVal);
-        }
+	_retVal = RegDeleteKeyW(myKey, __unicode16StringVal(subKeyStringZ));
+#else
+	_retVal = RegDeleteKeyExW(myKey,
+		    __unicode16StringVal(subKeyStringZ),
+		    _flags,
+		    0); // reserved
+#endif
+	if (_retVal == ERROR_SUCCESS) {
+	    RETURN (true);
+	}
+	if ((_retVal != ERROR_PATH_NOT_FOUND)
+	 && (_retVal != ERROR_FILE_NOT_FOUND)) {
+	    errorNumber = __MKSMALLINT(_retVal);
+	}
     }
 out:;
 %}.
 
     errorNumber notNil ifTrue:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError.
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError.
     ].
     ^ false
 
@@ -15827,24 +15740,24 @@
     int _retVal;
 
     if (__isExternalAddressLike(__INST(handle)) && __isStringLike(hostName)) {
-        myKey = (HKEY)__externalAddressVal(__INST(handle));
-        if ((_retVal = RegConnectRegistryA(__stringVal(hostName), myKey, &remoteKey)) == ERROR_SUCCESS) {
-            remoteHandle = __MKEXTERNALADDRESS(remoteKey);
-        } else {
-            if ((_retVal != ERROR_PATH_NOT_FOUND)
-             && (_retVal != ERROR_FILE_NOT_FOUND)) {
-                errorNumber = __MKSMALLINT(_retVal);
-            }
-        }
+	myKey = (HKEY)__externalAddressVal(__INST(handle));
+	if ((_retVal = RegConnectRegistryA(__stringVal(hostName), myKey, &remoteKey)) == ERROR_SUCCESS) {
+	    remoteHandle = __MKEXTERNALADDRESS(remoteKey);
+	} else {
+	    if ((_retVal != ERROR_PATH_NOT_FOUND)
+	     && (_retVal != ERROR_FILE_NOT_FOUND)) {
+		errorNumber = __MKSMALLINT(_retVal);
+	    }
+	}
     }
 %}.
     remoteHandle notNil ifTrue:[
-        newEntry := self class basicNew setHandle:remoteHandle path:path.
-        newEntry registerForFinalization.
-        ^ newEntry.
+	newEntry := self class basicNew setHandle:remoteHandle path:path.
+	newEntry registerForFinalization.
+	^ newEntry.
     ].
     errorNumber notNil ifTrue:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError.
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError.
     ].
     ^ nil
 
@@ -15891,30 +15804,30 @@
 
     if (__isExternalAddressLike(__INST(handle))
      && __isSmallInteger(subKeyIndex)) {
-        myKey = (HKEY)__externalAddressVal(__INST(handle));
-        if ((_retVal = RegEnumKeyExA(myKey, __intVal(subKeyIndex),
-                         nameBuffer, &nameSize,
-                         NULL,
-                         classNameBuffer, &classNameSize,
-                         &modificationTime)) == ERROR_SUCCESS) {
-            nameBuffer[nameSize] = '\0';
-            classNameBuffer[classNameSize] = '\0';
-            subKeyName = __MKSTRING(nameBuffer);
-            subKeyClassName = __MKSTRING(classNameBuffer);
-        } else {
-            if ((_retVal != ERROR_PATH_NOT_FOUND)
-             && (_retVal != ERROR_FILE_NOT_FOUND)
-             && (_retVal != ERROR_NO_MORE_ITEMS)) {
-                errorNumber = __MKSMALLINT(_retVal);
-            }
-        }
+	myKey = (HKEY)__externalAddressVal(__INST(handle));
+	if ((_retVal = RegEnumKeyExA(myKey, __intVal(subKeyIndex),
+			 nameBuffer, &nameSize,
+			 NULL,
+			 classNameBuffer, &classNameSize,
+			 &modificationTime)) == ERROR_SUCCESS) {
+	    nameBuffer[nameSize] = '\0';
+	    classNameBuffer[classNameSize] = '\0';
+	    subKeyName = __MKSTRING(nameBuffer);
+	    subKeyClassName = __MKSTRING(classNameBuffer);
+	} else {
+	    if ((_retVal != ERROR_PATH_NOT_FOUND)
+	     && (_retVal != ERROR_FILE_NOT_FOUND)
+	     && (_retVal != ERROR_NO_MORE_ITEMS)) {
+		errorNumber = __MKSMALLINT(_retVal);
+	    }
+	}
     }
 %}.
     subKeyName notNil ifTrue:[
-        ^ self subKeyNamed:subKeyName.
+	^ self subKeyNamed:subKeyName.
     ].
     errorNumber notNil ifTrue:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError.
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError.
     ].
     ^ nil
 
@@ -15943,30 +15856,30 @@
 
     if (__isExternalAddressLike(__INST(handle))
      && __isSmallInteger(subKeyIndex)) {
-        myKey = (HKEY)__externalAddressVal(__INST(handle));
-        if ((_retVal = RegEnumKeyExA(myKey, __intVal(subKeyIndex),
-                         nameBuffer, &nameSize,
-                         NULL,
-                         classNameBuffer, &classNameSize,
-                         &modificationTime)) == ERROR_SUCCESS) {
-            nameBuffer[nameSize] = '\0';
-            classNameBuffer[classNameSize] = '\0';
-            subKeyName = __MKSTRING(nameBuffer);
-            subKeyClassName = __MKSTRING(classNameBuffer);
-        } else {
-            if ((_retVal != ERROR_PATH_NOT_FOUND)
-             && (_retVal != ERROR_FILE_NOT_FOUND)
-             && (_retVal != ERROR_NO_MORE_ITEMS)) {
-                errorNumber = __MKSMALLINT(_retVal);
-            }
-        }
+	myKey = (HKEY)__externalAddressVal(__INST(handle));
+	if ((_retVal = RegEnumKeyExA(myKey, __intVal(subKeyIndex),
+			 nameBuffer, &nameSize,
+			 NULL,
+			 classNameBuffer, &classNameSize,
+			 &modificationTime)) == ERROR_SUCCESS) {
+	    nameBuffer[nameSize] = '\0';
+	    classNameBuffer[classNameSize] = '\0';
+	    subKeyName = __MKSTRING(nameBuffer);
+	    subKeyClassName = __MKSTRING(classNameBuffer);
+	} else {
+	    if ((_retVal != ERROR_PATH_NOT_FOUND)
+	     && (_retVal != ERROR_FILE_NOT_FOUND)
+	     && (_retVal != ERROR_NO_MORE_ITEMS)) {
+		errorNumber = __MKSMALLINT(_retVal);
+	    }
+	}
     }
 %}.
     subKeyName notNil ifTrue:[
-        ^ {subKeyName . subKeyClassName}.
+	^ {subKeyName . subKeyClassName}.
     ].
     errorNumber notNil ifTrue:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError.
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError.
     ].
     ^ nil
 
@@ -16004,9 +15917,9 @@
     "return a new registry entry below mySelf with the given subKey.
      Return nil if no such key exists.
      flags may be one of:
-        #KEY_WOW64_64KEY to force access to the 64Bit Windows key,
-        #KEY_WOW64_32KEY to force access to the 32Bit Windows key,
-        or nil, to access the key (32/64) for the current application"
+	#KEY_WOW64_64KEY to force access to the 64Bit Windows key,
+	#KEY_WOW64_32KEY to force access to the 32Bit Windows key,
+	or nil, to access the key (32/64) for the current application"
 
 
     ^ self subKeyNamed:subKeyString flags:flags createIfAbsent:false
@@ -16017,9 +15930,9 @@
      If no such key exists and createIfAbsent is true, the key is created.
      Otherwise, nil is returned.
      flags may be one of:
-        #KEY_WOW64_64KEY to force access to the 64Bit Windows key,
-        #KEY_WOW64_32KEY to force access to the 32Bit Windows key,
-        or nil, to access the key (32/64) for the current application"
+	#KEY_WOW64_64KEY to force access to the 64Bit Windows key,
+	#KEY_WOW64_32KEY to force access to the 32Bit Windows key,
+	or nil, to access the key (32/64) for the current application"
 
     |subKeyStringZ newEntry subHandle errorNumber disposition|
 
@@ -16038,72 +15951,72 @@
     int _disposition = 0;
 
     if (flags != nil) {
-        if (flags == @symbol(KEY_WOW64_64KEY)) {
-            _flags = KEY_WOW64_64KEY;
-        } else if (flags == @symbol(KEY_WOW64_32KEY)) {
-            _flags = KEY_WOW64_32KEY;
-        } else {
-            errorNumber = @symbol(badArgument2);
-            goto out;
-        }
+	if (flags == @symbol(KEY_WOW64_64KEY)) {
+	    _flags = KEY_WOW64_64KEY;
+	} else if (flags == @symbol(KEY_WOW64_32KEY)) {
+	    _flags = KEY_WOW64_32KEY;
+	} else {
+	    errorNumber = @symbol(badArgument2);
+	    goto out;
+	}
     }
 
     if (__isExternalAddressLike(__INST(handle))
-        && __isUnicode16String(subKeyStringZ)) {
-        myKey = (HKEY)__externalAddressVal(__INST(handle));
-        if (createIfAbsent == true) {
-            _retVal = RegCreateKeyExW(myKey,
-                        __unicode16StringVal(subKeyStringZ),
-                        0,      // reserved
-                        NULL,   // class
-                        0,      // options
-                        KEY_ALL_ACCESS|_flags,   // rights
-                        NULL,   // securityAttributes - handle cannot be inherited
-                        &subKey,
-                        &_disposition);  // disposition (created vs. opened)
-            disposition = _disposition == REG_CREATED_NEW_KEY ? true : false;
-        } else {
-            _retVal = RegOpenKeyExW(
-                myKey,
-                __unicode16StringVal(subKeyStringZ),
-                0,                     
-                KEY_ALL_ACCESS|_flags,
-                &subKey);
-
-            if (!(_retVal == 0)) {
-                // try again with less permission
-                _retVal = RegOpenKeyExW(
-                    myKey,
-                    __unicode16StringVal(subKeyStringZ),
-                    0,                     
-                    KEY_READ |_flags,
-                    &subKey);
-            }
-
-            disposition = false;
-        }
-        if (_retVal == ERROR_SUCCESS) {
-            subHandle = __MKEXTERNALADDRESS(subKey);
-        } else {
-            if ((_retVal != ERROR_PATH_NOT_FOUND)
-             && (_retVal != ERROR_FILE_NOT_FOUND)) {
-                errorNumber = __MKSMALLINT(_retVal);
-            }
-        }
+	&& __isUnicode16String(subKeyStringZ)) {
+	myKey = (HKEY)__externalAddressVal(__INST(handle));
+	if (createIfAbsent == true) {
+	    _retVal = RegCreateKeyExW(myKey,
+			__unicode16StringVal(subKeyStringZ),
+			0,      // reserved
+			NULL,   // class
+			0,      // options
+			KEY_ALL_ACCESS|_flags,   // rights
+			NULL,   // securityAttributes - handle cannot be inherited
+			&subKey,
+			&_disposition);  // disposition (created vs. opened)
+	    disposition = _disposition == REG_CREATED_NEW_KEY ? true : false;
+	} else {
+	    _retVal = RegOpenKeyExW(
+		myKey,
+		__unicode16StringVal(subKeyStringZ),
+		0,
+		KEY_ALL_ACCESS|_flags,
+		&subKey);
+
+	    if (!(_retVal == 0)) {
+		// try again with less permission
+		_retVal = RegOpenKeyExW(
+		    myKey,
+		    __unicode16StringVal(subKeyStringZ),
+		    0,
+		    KEY_READ |_flags,
+		    &subKey);
+	    }
+
+	    disposition = false;
+	}
+	if (_retVal == ERROR_SUCCESS) {
+	    subHandle = __MKEXTERNALADDRESS(subKey);
+	} else {
+	    if ((_retVal != ERROR_PATH_NOT_FOUND)
+	     && (_retVal != ERROR_FILE_NOT_FOUND)) {
+		errorNumber = __MKSMALLINT(_retVal);
+	    }
+	}
     }
 out:;
 %}.
     subHandle notNil ifTrue:[
-        newEntry := self class basicNew
-                        setHandle:subHandle
-                        path:((path ? '?') , self class separator asString , subKeyString)
-                        isNew:disposition.
-
-        newEntry registerForFinalization.
-        ^ newEntry.
+	newEntry := self class basicNew
+			setHandle:subHandle
+			path:((path ? '?') , self class separator asString , subKeyString)
+			isNew:disposition.
+
+	newEntry registerForFinalization.
+	^ newEntry.
     ].
     errorNumber notNil ifTrue:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportProceedableError.
+	(OperatingSystem errorHolderForNumber:errorNumber) reportProceedableError.
     ].
     ^ nil
 
@@ -16133,11 +16046,11 @@
 
 defaultValue:datum
     "store a value; the value type depends upon the stored value:
-        ByteArray       -> REG_BINARY
-        String          -> REG_SZ
-        Array of string -> REG_MULTI_SZ
-        Integer         -> REG_DWORD
-        nil             -> REG_NONE
+	ByteArray       -> REG_BINARY
+	String          -> REG_SZ
+	Array of string -> REG_MULTI_SZ
+	Integer         -> REG_DWORD
+	nil             -> REG_NONE
     "
 
     ^ self valueNamed:'' put:datum
@@ -16159,18 +16072,18 @@
 
     if (__isExternalAddressLike(__INST(handle))
      && __isStringLike(aValueName)) {
-        myKey = (HKEY)__externalAddressVal(__INST(handle));
-        if ((_retVal = RegDeleteValueA(myKey, __stringVal(aValueName))) == ERROR_SUCCESS) {
-            RETURN (true);
-        }
-        if ((_retVal != ERROR_PATH_NOT_FOUND)
-         && (_retVal != ERROR_FILE_NOT_FOUND)) {
-            errorNumber = __MKSMALLINT(_retVal);
-        }
+	myKey = (HKEY)__externalAddressVal(__INST(handle));
+	if ((_retVal = RegDeleteValueA(myKey, __stringVal(aValueName))) == ERROR_SUCCESS) {
+	    RETURN (true);
+	}
+	if ((_retVal != ERROR_PATH_NOT_FOUND)
+	 && (_retVal != ERROR_FILE_NOT_FOUND)) {
+	    errorNumber = __MKSMALLINT(_retVal);
+	}
     }
 %}.
     errorNumber notNil ifTrue:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError.
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError.
     ].
     ^ false
 !
@@ -16190,25 +16103,25 @@
 
     if (__isExternalAddressLike(__INST(handle))
      && __isSmallInteger(valueIndex)) {
-        myKey = (HKEY)__externalAddressVal(__INST(handle));
-        if ((_retVal = RegEnumValueA(myKey, __intVal(valueIndex),
-                         nameBuffer, &nameSize,
-                         NULL,
-                         &valueType,
-                         NULL, NULL)) == ERROR_SUCCESS) {
-            nameBuffer[nameSize] = '\0';
-            valueName = __MKSTRING(nameBuffer);
-        } else {
-            if ((_retVal != ERROR_PATH_NOT_FOUND)
-             && (_retVal != ERROR_FILE_NOT_FOUND)
-             && (_retVal != ERROR_NO_MORE_ITEMS)) {
-                errorNumber = __MKSMALLINT(_retVal);
-            }
-        }
+	myKey = (HKEY)__externalAddressVal(__INST(handle));
+	if ((_retVal = RegEnumValueA(myKey, __intVal(valueIndex),
+			 nameBuffer, &nameSize,
+			 NULL,
+			 &valueType,
+			 NULL, NULL)) == ERROR_SUCCESS) {
+	    nameBuffer[nameSize] = '\0';
+	    valueName = __MKSTRING(nameBuffer);
+	} else {
+	    if ((_retVal != ERROR_PATH_NOT_FOUND)
+	     && (_retVal != ERROR_FILE_NOT_FOUND)
+	     && (_retVal != ERROR_NO_MORE_ITEMS)) {
+		errorNumber = __MKSMALLINT(_retVal);
+	    }
+	}
     }
 %}.
     errorNumber notNil ifTrue:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError.
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError.
     ].
     ^ valueName
 
@@ -16222,11 +16135,11 @@
 
 valueNamed:aValueName
     "retrieve a value; the returned object depends upon the type:
-        REG_BINARY      -> ByteArray
-        REG_SZ          -> String
-        REG_MULTI_SZ    -> Array of strings
-        REG_DWORD       -> Integer
-        REG_NONE        -> nil
+	REG_BINARY      -> ByteArray
+	REG_SZ          -> String
+	REG_MULTI_SZ    -> Array of strings
+	REG_DWORD       -> Integer
+	REG_NONE        -> nil
     "
 
     |stringArray retVal errorNumber|
@@ -16235,9 +16148,9 @@
     HKEY myKey;
     DWORD valueType;
     union {
-        DWORD dWord;
-        unsigned char dWordBytes[4];
-        unsigned char smallDataBuffer[1024*16];
+	DWORD dWord;
+	unsigned char dWordBytes[4];
+	unsigned char smallDataBuffer[1024*16];
     } quickData;
     int val;
     DWORD dataSize = sizeof(quickData);
@@ -16253,164 +16166,164 @@
 
     if (__isExternalAddressLike(__INST(handle))
      && __isStringLike(aValueName)) {
-        int ret;
-
-        myKey = (HKEY)__externalAddressVal(__INST(handle));
-
-        /*
-         * try to get it with one call ...
-         */
-        ret = RegQueryValueExA(myKey, __stringVal(aValueName),
-                         NULL,
-                         &valueType,
-                         (char *)&quickData,
-                         &dataSize);
+	int ret;
+
+	myKey = (HKEY)__externalAddressVal(__INST(handle));
+
+	/*
+	 * try to get it with one call ...
+	 */
+	ret = RegQueryValueExA(myKey, __stringVal(aValueName),
+			 NULL,
+			 &valueType,
+			 (char *)&quickData,
+			 &dataSize);
 #if 0
-        console_printf("get \"%s\": dataSize=%d ret=%d\n", __stringVal(aValueName), dataSize, ret);
-#endif
-        while (ret == ERROR_MORE_DATA) {
+	console_printf("get \"%s\": dataSize=%d ret=%d\n", __stringVal(aValueName), dataSize, ret);
+#endif
+	while (ret == ERROR_MORE_DATA) {
 #if 0
-            console_printf("ERROR_MORE_DATA dataSize=%d valueType=%d\n", dataSize, valueType);
-#endif
-            /*
-             * nope - need another one ...
-             */
-            if (myKey = HKEY_PERFORMANCE_DATA) {
-                dataSize = dataSize * 2;
-            }
-            switch (valueType) {
-                case REG_BINARY:
-                case REG_MULTI_SZ:
-                    dataBuffer = malloc(dataSize);;
-                    break;
-                case REG_SZ:
-                    dataBuffer = malloc(dataSize);
-                    break;
-                default:
-                    console_printf("RegistryEntry [warning]: unhandled valueType: %d\n", valueType);
-                    break;
-            }
-            if (dataBuffer) {
-                ret = RegQueryValueEx(myKey, __stringVal(aValueName),
-                                 NULL,
-                                 &valueType,
-                                 dataBuffer,
-                                 &dataSize);
-            } else {
-                break;
-            }
-            if (myKey != HKEY_PERFORMANCE_DATA) {
-                if (ret != ERROR_SUCCESS) break;
-            }
-        }
-
-        if (ret == ERROR_SUCCESS) {
+	    console_printf("ERROR_MORE_DATA dataSize=%d valueType=%d\n", dataSize, valueType);
+#endif
+	    /*
+	     * nope - need another one ...
+	     */
+	    if (myKey = HKEY_PERFORMANCE_DATA) {
+		dataSize = dataSize * 2;
+	    }
+	    switch (valueType) {
+		case REG_BINARY:
+		case REG_MULTI_SZ:
+		    dataBuffer = malloc(dataSize);;
+		    break;
+		case REG_SZ:
+		    dataBuffer = malloc(dataSize);
+		    break;
+		default:
+		    console_printf("RegistryEntry [warning]: unhandled valueType: %d\n", valueType);
+		    break;
+	    }
+	    if (dataBuffer) {
+		ret = RegQueryValueEx(myKey, __stringVal(aValueName),
+				 NULL,
+				 &valueType,
+				 dataBuffer,
+				 &dataSize);
+	    } else {
+		break;
+	    }
+	    if (myKey != HKEY_PERFORMANCE_DATA) {
+		if (ret != ERROR_SUCCESS) break;
+	    }
+	}
+
+	if (ret == ERROR_SUCCESS) {
 #if 0
-            console_printf("ERROR_SUCCESS dataSize=%d valueType=%d\n", dataSize, valueType);
-#endif
-            switch (valueType) {
-                case REG_NONE:
-                    /* RETURN (@symbol(none));  */
-                    retVal = nil;
-                    break;
-
-                case REG_BINARY:
-                    retVal = __MKBYTEARRAY(dataBuffer ? dataBuffer : quickData.smallDataBuffer, dataSize);
-                    break;
-
-                case REG_SZ:
-                case REG_EXPAND_SZ:
+	    console_printf("ERROR_SUCCESS dataSize=%d valueType=%d\n", dataSize, valueType);
+#endif
+	    switch (valueType) {
+		case REG_NONE:
+		    /* RETURN (@symbol(none));  */
+		    retVal = nil;
+		    break;
+
+		case REG_BINARY:
+		    retVal = __MKBYTEARRAY(dataBuffer ? dataBuffer : quickData.smallDataBuffer, dataSize);
+		    break;
+
+		case REG_SZ:
+		case REG_EXPAND_SZ:
 #ifdef USE_UNICODE
-                    retVal = __MKU16STRING(dataBuffer ? dataBuffer : quickData.smallDataBuffer);
-#else
-                    retVal = __MKSTRING(dataBuffer ? dataBuffer : quickData.smallDataBuffer);
-#endif
-                    break;
+		    retVal = __MKU16STRING(dataBuffer ? dataBuffer : quickData.smallDataBuffer);
+#else
+		    retVal = __MKSTRING(dataBuffer ? dataBuffer : quickData.smallDataBuffer);
+#endif
+		    break;
 
 #if 0
-                case REG_DWORD:
-                    /* int in native format */
-                    retVal = __MKUINT(quickData.dWord);
-                    break;
-#endif
-                case REG_DWORD_LITTLE_ENDIAN:
-                    val = quickData.dWordBytes[3];
-                    val = (val << 8) | quickData.dWordBytes[2];
-                    val = (val << 8) | quickData.dWordBytes[1];
-                    val = (val << 8) | quickData.dWordBytes[0];
-                    retVal = __MKUINT(val);
-                    break;
-
-                case REG_DWORD_BIG_ENDIAN:
-                    val = quickData.dWordBytes[0];
-                    val = (val << 8) | quickData.dWordBytes[1];
-                    val = (val << 8) | quickData.dWordBytes[2];
-                    val = (val << 8) | quickData.dWordBytes[3];
-                    retVal = __MKUINT(val);
-                    break;
-
-                case REG_MULTI_SZ:
-                    {
-                        CHAR *cp, *cp0;
-                        int ns, i;
-
-                        cp0 = dataBuffer ? dataBuffer : quickData.smallDataBuffer;
+		case REG_DWORD:
+		    /* int in native format */
+		    retVal = __MKUINT(quickData.dWord);
+		    break;
+#endif
+		case REG_DWORD_LITTLE_ENDIAN:
+		    val = quickData.dWordBytes[3];
+		    val = (val << 8) | quickData.dWordBytes[2];
+		    val = (val << 8) | quickData.dWordBytes[1];
+		    val = (val << 8) | quickData.dWordBytes[0];
+		    retVal = __MKUINT(val);
+		    break;
+
+		case REG_DWORD_BIG_ENDIAN:
+		    val = quickData.dWordBytes[0];
+		    val = (val << 8) | quickData.dWordBytes[1];
+		    val = (val << 8) | quickData.dWordBytes[2];
+		    val = (val << 8) | quickData.dWordBytes[3];
+		    retVal = __MKUINT(val);
+		    break;
+
+		case REG_MULTI_SZ:
+		    {
+			CHAR *cp, *cp0;
+			int ns, i;
+
+			cp0 = dataBuffer ? dataBuffer : quickData.smallDataBuffer;
 #if 0
-                        console_printf("**************\n");
-                        for (i=0;i<50;i++) {
-                          console_printf("%x ", cp0[i]);
-                        }
-                        console_printf("\n");
-                        for (i=0;i<50;i++) {
-                          if (cp0[i] == 0)
-                            console_printf("\n");
-                          else
-                            console_printf("%c", cp0[i]);
-                        }
-                        console_printf("\n");
-                        console_printf("**************\n");
-#endif
-                        cp = cp0;
-                        ns = 0;
-                        while (*cp) {
-                            while (*cp++) ;;
-                            ns++;
-                        }
-                        stringArray = __ARRAY_NEW_INT(ns);
-
-                        i = 0;
-                        while (*cp0) {
-                            OBJ s;
-                            CHAR *cp;
-
-                            cp = cp0;
-                            while (*cp++) ;;
+			console_printf("**************\n");
+			for (i=0;i<50;i++) {
+			  console_printf("%x ", cp0[i]);
+			}
+			console_printf("\n");
+			for (i=0;i<50;i++) {
+			  if (cp0[i] == 0)
+			    console_printf("\n");
+			  else
+			    console_printf("%c", cp0[i]);
+			}
+			console_printf("\n");
+			console_printf("**************\n");
+#endif
+			cp = cp0;
+			ns = 0;
+			while (*cp) {
+			    while (*cp++) ;;
+			    ns++;
+			}
+			stringArray = __ARRAY_NEW_INT(ns);
+
+			i = 0;
+			while (*cp0) {
+			    OBJ s;
+			    CHAR *cp;
+
+			    cp = cp0;
+			    while (*cp++) ;;
 #ifdef USE_UNICODE
-                            s = __MKU16STRING(cp0); __ArrayInstPtr(stringArray)->a_element[i] = s; __STORE(stringArray, s);
-#else
-                            s = __MKSTRING(cp0); __ArrayInstPtr(stringArray)->a_element[i] = s; __STORE(stringArray, s);
-#endif
-                            cp0 = cp;
-                            i++;
-                        }
-                        retVal = stringArray;
-                        break;
-                    }
-                default:
-                    console_printf("RegistryEntry [warning]: unhandled valueType: %d\n", valueType);
-                    break;
-            }
-        } else {
-            if ((ret != ERROR_PATH_NOT_FOUND)
-             && (ret != ERROR_FILE_NOT_FOUND)) {
-                errorNumber = __MKSMALLINT(ret);
-            }
-        }
+			    s = __MKU16STRING(cp0); __ArrayInstPtr(stringArray)->a_element[i] = s; __STORE(stringArray, s);
+#else
+			    s = __MKSTRING(cp0); __ArrayInstPtr(stringArray)->a_element[i] = s; __STORE(stringArray, s);
+#endif
+			    cp0 = cp;
+			    i++;
+			}
+			retVal = stringArray;
+			break;
+		    }
+		default:
+		    console_printf("RegistryEntry [warning]: unhandled valueType: %d\n", valueType);
+		    break;
+	    }
+	} else {
+	    if ((ret != ERROR_PATH_NOT_FOUND)
+	     && (ret != ERROR_FILE_NOT_FOUND)) {
+		errorNumber = __MKSMALLINT(ret);
+	    }
+	}
     }
     if (dataBuffer) free(dataBuffer);
 %}.
     errorNumber notNil ifTrue:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError.
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError.
     ].
 
     ^ retVal
@@ -16425,11 +16338,11 @@
 
 valueNamed:aValueName put:datum
     "store a value; the value type depends upon the stored value:
-        ByteArray       -> REG_BINARY
-        String          -> REG_SZ
-        Array of string -> REG_MULTI_SZ
-        Integer         -> REG_DWORD
-        nil             -> REG_NONE
+	ByteArray       -> REG_BINARY
+	String          -> REG_SZ
+	Array of string -> REG_MULTI_SZ
+	Integer         -> REG_DWORD
+	nil             -> REG_NONE
     "
 
     |data stringArray errorNumber|
@@ -16443,99 +16356,99 @@
 
     if (__isExternalAddressLike(__INST(handle))
      && __isStringLike(aValueName)) {
-        int ret;
-        OBJ cls;
-
-        myKey = (HKEY)__externalAddressVal(__INST(handle));
-
-        if (datum == nil) {
-            valueType = REG_NONE;
-            dataSize = 0;
-        } else if (__isSmallInteger(datum)) {
-            valueType = REG_DWORD;
-            val = __intVal(datum);
-            dataPointer = (unsigned char *)(&val);
-            dataSize = sizeof(val);
-        } else if (__isStringLike(datum)) {
-            valueType = REG_SZ;
-            dataPointer = __stringVal(datum);
-            dataSize = __stringSize(datum) + 1;
-        } else if (__Class(datum) == ByteArray) {
-            valueType = REG_BINARY;
-            dataPointer = __ByteArrayInstPtr(datum)->ba_element;
-            dataSize = __byteArraySize(datum);
-        } else if (__Class(datum) == LargeInteger) {
-            valueType = REG_DWORD;
-            val = __longIntVal(datum);
-            if (val) {
-                dataPointer = (unsigned char *)(&val);
-                dataSize = sizeof(val);
-            } else {
-                datumOk = 0;
-            }
-        } else if (__Class(datum) == Array) {
-            int i = 0, ns = 0, totalSize = 0;
-
-            valueType = REG_MULTI_SZ;
-
-            /*
-             * must allocate a local buffer
-             * find size ...
-             */
-            for (i=0; i<__arraySize(datum); i++) {
-                OBJ s = __ArrayInstPtr(datum)->a_element[i];
-
-                if (__isStringLike(s)) {
-                    totalSize += __stringSize(s) + 1;
-                } else {
-                    datumOk = 0;
-                    break;
-                }
-                ns++;
-            }
-            if (datumOk) {
-                char *cp;
-
-                /*
-                 * allocate and fill...
-                 */
-                totalSize ++;
-                dataPointer = (char *)(malloc(totalSize));
-                mustFreeData = 1;
-                cp = dataPointer;
-                for (i=0; i<__arraySize(datum); i++) {
-                    OBJ s = __ArrayInstPtr(datum)->a_element[i];
-
-                    strcpy(cp, __stringVal(s));
-                    cp += __stringSize(s);
-                    *cp++ = '\0';
-                }
-                *cp++ = '\0';
-                dataSize = totalSize;
-            }
-        } else {
-            datumOk = 0;
-        }
-
-        if (datumOk) {
-            ret = RegSetValueExA(myKey, __stringVal(aValueName),
-                                0, valueType,
-                                dataPointer, dataSize);
-            if (mustFreeData) {
-                free(dataPointer);
-            }
-            if (ret == ERROR_SUCCESS) {
-                RETURN (true);
-            }
-            if ((ret != ERROR_PATH_NOT_FOUND)
-             && (ret != ERROR_FILE_NOT_FOUND)) {
-                errorNumber = __MKSMALLINT(ret);
-            }
-        }
+	int ret;
+	OBJ cls;
+
+	myKey = (HKEY)__externalAddressVal(__INST(handle));
+
+	if (datum == nil) {
+	    valueType = REG_NONE;
+	    dataSize = 0;
+	} else if (__isSmallInteger(datum)) {
+	    valueType = REG_DWORD;
+	    val = __intVal(datum);
+	    dataPointer = (unsigned char *)(&val);
+	    dataSize = sizeof(val);
+	} else if (__isStringLike(datum)) {
+	    valueType = REG_SZ;
+	    dataPointer = __stringVal(datum);
+	    dataSize = __stringSize(datum) + 1;
+	} else if (__Class(datum) == ByteArray) {
+	    valueType = REG_BINARY;
+	    dataPointer = __ByteArrayInstPtr(datum)->ba_element;
+	    dataSize = __byteArraySize(datum);
+	} else if (__Class(datum) == LargeInteger) {
+	    valueType = REG_DWORD;
+	    val = __longIntVal(datum);
+	    if (val) {
+		dataPointer = (unsigned char *)(&val);
+		dataSize = sizeof(val);
+	    } else {
+		datumOk = 0;
+	    }
+	} else if (__Class(datum) == Array) {
+	    int i = 0, ns = 0, totalSize = 0;
+
+	    valueType = REG_MULTI_SZ;
+
+	    /*
+	     * must allocate a local buffer
+	     * find size ...
+	     */
+	    for (i=0; i<__arraySize(datum); i++) {
+		OBJ s = __ArrayInstPtr(datum)->a_element[i];
+
+		if (__isStringLike(s)) {
+		    totalSize += __stringSize(s) + 1;
+		} else {
+		    datumOk = 0;
+		    break;
+		}
+		ns++;
+	    }
+	    if (datumOk) {
+		char *cp;
+
+		/*
+		 * allocate and fill...
+		 */
+		totalSize ++;
+		dataPointer = (char *)(malloc(totalSize));
+		mustFreeData = 1;
+		cp = dataPointer;
+		for (i=0; i<__arraySize(datum); i++) {
+		    OBJ s = __ArrayInstPtr(datum)->a_element[i];
+
+		    strcpy(cp, __stringVal(s));
+		    cp += __stringSize(s);
+		    *cp++ = '\0';
+		}
+		*cp++ = '\0';
+		dataSize = totalSize;
+	    }
+	} else {
+	    datumOk = 0;
+	}
+
+	if (datumOk) {
+	    ret = RegSetValueExA(myKey, __stringVal(aValueName),
+				0, valueType,
+				dataPointer, dataSize);
+	    if (mustFreeData) {
+		free(dataPointer);
+	    }
+	    if (ret == ERROR_SUCCESS) {
+		RETURN (true);
+	    }
+	    if ((ret != ERROR_PATH_NOT_FOUND)
+	     && (ret != ERROR_FILE_NOT_FOUND)) {
+		errorNumber = __MKSMALLINT(ret);
+	    }
+	}
     }
 %}.
     errorNumber notNil ifTrue:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError.
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError.
     ].
     ^ false
 
@@ -16556,14 +16469,14 @@
 
     idx := 0.
     [true] whileTrue:[
-        subEntry := self subKeyAtIndex:idx.
-        subEntry isNil ifTrue:[
-            ^self
-        ].
-        aBlock value:subEntry.
-        subEntry allSubKeysDo:aBlock.
-        subEntry close.
-        idx := idx + 1.
+	subEntry := self subKeyAtIndex:idx.
+	subEntry isNil ifTrue:[
+	    ^self
+	].
+	aBlock value:subEntry.
+	subEntry allSubKeysDo:aBlock.
+	subEntry close.
+	idx := idx + 1.
     ]
 
     "
@@ -16571,7 +16484,7 @@
 
      top := self key:'HKEY_LOCAL_MACHINE'.
      top allSubKeysDo:[:subEntry |
-        Transcript showCR:subEntry path
+	Transcript showCR:subEntry path
      ]
     "
 !
@@ -16583,12 +16496,12 @@
 
     idx := 0.
     [true] whileTrue:[
-        nameAndClassNameOrNil := self subKeyNameAndClassAtIndex:idx.
-        nameAndClassNameOrNil isNil ifTrue:[
-            ^self
-        ].
-        aTwoArgBlock value:nameAndClassNameOrNil first value:nameAndClassNameOrNil second.
-        idx := idx + 1.
+	nameAndClassNameOrNil := self subKeyNameAndClassAtIndex:idx.
+	nameAndClassNameOrNil isNil ifTrue:[
+	    ^self
+	].
+	aTwoArgBlock value:nameAndClassNameOrNil first value:nameAndClassNameOrNil second.
+	idx := idx + 1.
     ]
 
     "
@@ -16596,7 +16509,7 @@
 
      top := self key:'HKEY_LOCAL_MACHINE'.
      top subKeyNamesAndClassesDo:[:nm :cls |
-        Transcript showCR:('name: ',nm,' class: ',cls)
+	Transcript showCR:('name: ',nm,' class: ',cls)
      ]
     "
 !
@@ -16628,13 +16541,13 @@
 
     idx := 0.
     [true] whileTrue:[
-        subEntry := self subKeyAtIndex:idx.
-        subEntry isNil ifTrue:[
-            ^self
-        ].
-        aBlock value:subEntry.
-        subEntry close.
-        idx := idx + 1.
+	subEntry := self subKeyAtIndex:idx.
+	subEntry isNil ifTrue:[
+	    ^self
+	].
+	aBlock value:subEntry.
+	subEntry close.
+	idx := idx + 1.
     ]
 
     "
@@ -16642,7 +16555,7 @@
 
      top := self key:'HKEY_LOCAL_MACHINE'.
      top subKeysDo:[:subEntry |
-        Transcript showCR:subEntry path
+	Transcript showCR:subEntry path
      ]
     "
     "
@@ -16650,11 +16563,11 @@
 
      top := self key:'HKEY_LOCAL_MACHINE'.
      OSErrorHolder noPermissionsSignal handle:[:ex |
-        ex proceed
+	ex proceed
      ] do:[
-         top subKeysDo:[:subEntry |
-            Transcript showCR:subEntry path
-         ]
+	 top subKeysDo:[:subEntry |
+	    Transcript showCR:subEntry path
+	 ]
      ]
     "
 !
@@ -16663,7 +16576,7 @@
     "evaluate aBlock for all value names"
 
     ^ Array streamContents:[:s |
-        self valueNamesDo:[:nm | s nextPut:nm]
+	self valueNamesDo:[:nm | s nextPut:nm]
     ].
 
     "Created: / 18-01-2011 / 20:24:52 / cg"
@@ -16673,7 +16586,7 @@
     "evaluate aBlock for all value names"
 
     self valueNamesDo:[:nm |
-        aBlock value:nm value:(self valueNamed:nm)
+	aBlock value:nm value:(self valueNamed:nm)
     ]
 
     "
@@ -16681,7 +16594,7 @@
 
      key := self key:'HKEY_LOCAL_MACHINE\SOFTWARE\eXept\Smalltalk/X'.
      key valueNamesAndValuesDo:[:nm :val |
-        Transcript showCR:(nm , ' -> ' , val storeString).
+	Transcript showCR:(nm , ' -> ' , val storeString).
      ]
     "
 !
@@ -16693,12 +16606,12 @@
 
     idx := 0.
     [true] whileTrue:[
-        valueName := self valueNameAtIndex:idx.
-        valueName isNil ifTrue:[
-            ^self
-        ].
-        aBlock value:valueName.
-        idx := idx + 1.
+	valueName := self valueNameAtIndex:idx.
+	valueName isNil ifTrue:[
+	    ^self
+	].
+	aBlock value:valueName.
+	idx := idx + 1.
     ]
 ! !
 
@@ -16718,9 +16631,9 @@
     HKEY myKey;
 
     if (__isExternalAddressLike(__INST(handle))) {
-        myKey = (HKEY)(__externalAddressVal(__INST(handle)));
-        __INST(handle) = nil;
-        RegCloseKey(myKey);
+	myKey = (HKEY)(__externalAddressVal(__INST(handle)));
+	__INST(handle) = nil;
+	RegCloseKey(myKey);
     }
 %}
 !
@@ -16733,7 +16646,7 @@
     "some entry has been collected - close it"
 
     handle notNil ifTrue:[
-        self closeKey.
+	self closeKey.
     ]
 
     "Created: / 19.5.1999 / 22:39:52 / cg"
@@ -16744,10 +16657,10 @@
 
 printOn:aStream
     aStream
-        nextPutAll:self className;
-        nextPut:$(;
-        nextPutAll:path;
-        nextPut:$).
+	nextPutAll:self className;
+	nextPut:$(;
+	nextPutAll:path;
+	nextPut:$).
 ! !
 
 !Win32OperatingSystem::RegistryEntry methodsFor:'private'!
@@ -16778,7 +16691,7 @@
 
     key = (HKEY)__longIntVal(integerHandleValue);
     if (! key) {
-        RETURN (nil);
+	RETURN (nil);
     }
 
     t = __MKEXTERNALADDRESS(key); __INST(handle) = t; __STORE(self, t);
@@ -16870,90 +16783,90 @@
     int 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));
-        if (extPtr == NULL) goto bad;
-        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));
+	if (extPtr == NULL) goto bad;
+	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;
-        // do not cast to INT - will loose sign bit then!
-        ok = (int)(STX_API_NOINT_CALL5( "ReadFile", ReadFile, hFile, extPtr, cntWanted, &cntRead, 0 /* lpOverlapped */));
+	__threadErrno = 0;
+	// do not cast to INT - will loose sign bit then!
+	ok = (int)(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
     ].
 
     "
@@ -16977,48 +16890,48 @@
     INT t;
 
     if ((hFile == 0) || (hFile == INVALID_HANDLE_VALUE)) {
-        errSym = @symbol(errorNotOpen);
-        goto bad;
+	errSym = @symbol(errorNotOpen);
+	goto bad;
     }
 
 #if 0
     if (ioctlsocket((SOCKET)hFile, FIONREAD, &res)==0) {
-        /* its a socket */
-        if (res > 0) {
-            RETURN ( false );
-        }
+	/* its a socket */
+	if (res > 0) {
+	    RETURN ( false );
+	}
     }
     if (PeekNamedPipe(hFile, 0, 0, 0, &res, 0)) {
-        /* its a namedPipe */
-        if (res > 0) {
-            RETURN ( false );
-        }
+	/* its a namedPipe */
+	if (res > 0) {
+	    RETURN ( false );
+	}
     }
 #endif
     if (__isSmallInteger(millis)) {
-        t = __intVal(millis);
+	t = __intVal(millis);
     } else {
-        t = INFINITE;
+	t = INFINITE;
     }
 
     do {
-        __threadErrno = 0;
-        res = WaitForSingleObject(hFile, t);
+	__threadErrno = 0;
+	res = WaitForSingleObject(hFile, t);
     } while (__threadErrno == EINTR);
 
     switch (res) {
-        case WAIT_OBJECT_0:
-            /* signalled */
-            RETURN ( false );
-
-        case WAIT_TIMEOUT:
-            /* signalled */
-            RETURN ( true );
-
-        default:
-        case WAIT_ABANDONED:
-            errorNumber = __mkSmallInteger( __WIN32_ERR(GetLastError()) );
-            goto bad;
+	case WAIT_OBJECT_0:
+	    /* signalled */
+	    RETURN ( false );
+
+	case WAIT_TIMEOUT:
+	    /* signalled */
+	    RETURN ( true );
+
+	default:
+	case WAIT_ABANDONED:
+	    errorNumber = __mkSmallInteger( __WIN32_ERR(GetLastError()) );
+	    goto bad;
     }
 
 bad: ;
@@ -17033,9 +16946,9 @@
 
 seekTo:newPosition from:whence
     "whence is one of:
-        #begin
-        #current
-        #end
+	#begin
+	#current
+	#end
     "
 
     |errSym errorNumber|
@@ -17047,24 +16960,24 @@
     __uint64__ pos64, newPos64;
 
     if ((hFile == 0) || (hFile == INVALID_HANDLE_VALUE)) {
-        errSym = @symbol(errorNotOpen);
-        goto bad;
+	errSym = @symbol(errorNotOpen);
+	goto bad;
     }
 
     if (whence == @symbol(begin)) {
-        moveHow = FILE_BEGIN;
+	moveHow = FILE_BEGIN;
     } else if (whence == @symbol(current)) {
-        moveHow = FILE_CURRENT;
+	moveHow = FILE_CURRENT;
     } else if (whence == @symbol(end)) {
-        moveHow = FILE_END;
+	moveHow = FILE_END;
     } else {
-        errSym = @symbol(badArgument2);
-        goto bad;
+	errSym = @symbol(badArgument2);
+	goto bad;
     }
 
     if (__signedLong64IntVal(newPosition, &pos64) == 0) {
-        errSym = @symbol(badArgument);
-        goto bad;
+	errSym = @symbol(badArgument);
+	goto bad;
     }
 #if __POINTER_SIZE__ == 8
     posLo = pos64 & 0xFFFFFFFF;
@@ -17075,18 +16988,18 @@
 #endif
     posLo = SetFilePointer(hFile, posLo, &posHi, moveHow);
     if (posLo == 0xFFFFFFFF) {
-        int lastError;
-
-        /* can be either an error, or a valid low-word */
-        lastError = GetLastError();
-        if (lastError != NO_ERROR) {
-            errorNumber = __mkSmallInteger( __WIN32_ERR(lastError) );
-            goto bad;
-        }
+	int lastError;
+
+	/* can be either an error, or a valid low-word */
+	lastError = GetLastError();
+	if (lastError != NO_ERROR) {
+	    errorNumber = __mkSmallInteger( __WIN32_ERR(lastError) );
+	    goto bad;
+	}
     }
 
     if (posHi == 0) {
-        RETURN (__MKUINT( posLo ));
+	RETURN (__MKUINT( posLo ));
     }
 #if __POINTER_SIZE__ == 8
     newPos64 = (__uint64__)posLo | ((__uint64__)posHi << 32);
@@ -17101,9 +17014,9 @@
 %}.
 
     errorNumber isNil ifTrue:[
-        self error:'invalid argument(s): ', errSym.
+	self error:'invalid argument(s): ', errSym.
     ] ifFalse:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError
     ].
 !
 
@@ -17124,84 +17037,84 @@
     int 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));
-        if (extPtr == NULL) goto bad;
-        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));
+	if (extPtr == NULL) goto bad;
+	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;
-        // do not cast to INT - will loose sign bit then!
-        ok = (int)(STX_API_NOINT_CALL5( "WriteFile", WriteFile, hFile, extPtr, cntWanted, &cntWritten, 0 /* lpOverlapped */));
+	__threadErrno = 0;
+	// do not cast to INT - will loose sign bit then!
+	ok = (int)(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
     ].
 
     "
@@ -17251,8 +17164,8 @@
     DisplayTypeMappingTable := Dictionary new.
 
     symbTable keysAndValuesDo:[:aSYMB :anINT |
-        DisplayTypeMappingTable at: aSYMB put: anINT.
-        DisplayTypeMappingTable at: anINT put: aSYMB. "/ vice versa
+	DisplayTypeMappingTable at: aSYMB put: anINT.
+	DisplayTypeMappingTable at: anINT put: aSYMB. "/ vice versa
     ].
     ^ DisplayTypeMappingTable
 !
@@ -17274,8 +17187,8 @@
     ScopeMappingTable := Dictionary new.
 
     symbTable keysAndValuesDo:[:aSYMB :anINT |
-        ScopeMappingTable at: aSYMB put: anINT.
-        ScopeMappingTable at: anINT put: aSYMB. "/ vice versa
+	ScopeMappingTable at: aSYMB put: anINT.
+	ScopeMappingTable at: anINT put: aSYMB. "/ vice versa
     ].
     ^ ScopeMappingTable
 !
@@ -17297,8 +17210,8 @@
     TypeMappingTable := Dictionary new.
 
     symbTable keysAndValuesDo:[:aSYMB :anINT |
-        TypeMappingTable at: aSYMB put: anINT.
-        TypeMappingTable at: anINT put: aSYMB. "/ vice versa
+	TypeMappingTable at: aSYMB put: anINT.
+	TypeMappingTable at: anINT put: aSYMB. "/ vice versa
     ].
     ^ TypeMappingTable
 !
@@ -17323,8 +17236,8 @@
     UsageMappingTable := Dictionary new.
 
     symbTable keysAndValuesDo:[:aSYMB :anINT |
-        UsageMappingTable at: aSYMB put: anINT.
-        UsageMappingTable at: anINT put: aSYMB. "/ vice versa
+	UsageMappingTable at: aSYMB put: anINT.
+	UsageMappingTable at: anINT put: aSYMB. "/ vice versa
     ].
     ^ UsageMappingTable
 ! !
@@ -17340,25 +17253,25 @@
      and nil is returned.
 
     self fetchResourcesStartingAt: nil withScope: #GLOBALNET type: #ANY usage: 0
-        onError: [:err| Transcript showCR: err ].
+	onError: [:err| Transcript showCR: err ].
     "
     | stream networkResources |
 
     [
-        stream := self openAt: aNetworkResourceOrNil
-            withScope: aScope type: aType usage: aUsage onError: aBlock.
-
-        stream notNil ifTrue:[
-            |next|
-
-            networkResources := OrderedCollection new.
-
-            [ (next := stream nextOrNil) notNil ] whileTrue:[
-                networkResources add:next.
-            ].
-        ]
+	stream := self openAt: aNetworkResourceOrNil
+	    withScope: aScope type: aType usage: aUsage onError: aBlock.
+
+	stream notNil ifTrue:[
+	    |next|
+
+	    networkResources := OrderedCollection new.
+
+	    [ (next := stream nextOrNil) notNil ] whileTrue:[
+		networkResources add:next.
+	    ].
+	]
     ] ensure:[
-        stream notNil ifTrue:[ stream close ].
+	stream notNil ifTrue:[ stream close ].
     ].
     ^ networkResources.
 !
@@ -17371,17 +17284,17 @@
      and nil is returned.
 
     self fetchSystemResourcesWithScope: #GLOBALNET type: #ANY usage: 0
-        onError: [:err| Transcript showCR: err ].
+	onError: [:err| Transcript showCR: err ].
 
     self fetchSystemResourcesWithScope: #REMEMBERED type: #DISK usage: 0
-        onError: [:err| Transcript showCR: err ].
+	onError: [:err| Transcript showCR: err ].
 
     self fetchSystemResourcesWithScope: #REMEMBERED type: #ANY usage: 0
-        onError: [:err| Transcript showCR: err ].
+	onError: [:err| Transcript showCR: err ].
     "
 
     ^ self fetchResourcesStartingAt: nil
-            withScope: aScope type: aType usage: aUsage onError: aBlock
+	    withScope: aScope type: aType usage: aUsage onError: aBlock
 !
 
 fetchVirtualDrives
@@ -17408,39 +17321,39 @@
 
     "/ map symbols to integer values.. on error an exception is raised
     aScope isInteger ifTrue:[ enumScope := aScope ]
-                    ifFalse:[ enumScope := self scopeMappingTable at:aScope ].
+		    ifFalse:[ enumScope := self scopeMappingTable at:aScope ].
 
     aUsage isInteger ifTrue:[ enumUsage := aUsage ]
-                    ifFalse:[ enumUsage := self usageMappingTable at:aUsage ].
+		    ifFalse:[ enumUsage := self usageMappingTable at:aUsage ].
 
     aType isInteger ifTrue:[ enumType := aType ]
-                   ifFalse:[ enumType := self typeMappingTable at:aType ].
+		   ifFalse:[ enumType := self typeMappingTable at:aType ].
 
     aResourceOrNil notNil ifTrue:[ | checkAndGetString |
-        resScope := aResourceOrNil scope.
-        resScope isInteger ifFalse:[ resScope := self scopeMappingTable at:resScope ].
-
-        resType := aResourceOrNil type.
-        resType isInteger ifFalse:[ resType := self typeMappingTable at: resType ].
-
-        resUsage := aResourceOrNil usage.
-        resUsage isInteger ifFalse:[ resUsage := self usageMappingTable at: resUsage ].
-
-        resDisplayType := aResourceOrNil displayType.
-        resDisplayType isInteger ifFalse:[ resDisplayType := self displayTypeMappingTable at:resDisplayType ].
-
-        checkAndGetString := [: aString| |string|
-            aString notNil ifTrue:[
-                self isUsingUnicode
-                    ifTrue: [ string := aString asUnicode16String  ]
-                    ifFalse:[ string := aString asSingleByteString ].
-            ].
-            string
-        ].
-        resRemoteName  := checkAndGetString value:( aResourceOrNil remoteName ).
-        resLocalName   := checkAndGetString value:( aResourceOrNil localName ).
-        resComment     := checkAndGetString value:( aResourceOrNil comment ).
-        resProvider    := checkAndGetString value:( aResourceOrNil provider ).
+	resScope := aResourceOrNil scope.
+	resScope isInteger ifFalse:[ resScope := self scopeMappingTable at:resScope ].
+
+	resType := aResourceOrNil type.
+	resType isInteger ifFalse:[ resType := self typeMappingTable at: resType ].
+
+	resUsage := aResourceOrNil usage.
+	resUsage isInteger ifFalse:[ resUsage := self usageMappingTable at: resUsage ].
+
+	resDisplayType := aResourceOrNil displayType.
+	resDisplayType isInteger ifFalse:[ resDisplayType := self displayTypeMappingTable at:resDisplayType ].
+
+	checkAndGetString := [: aString| |string|
+	    aString notNil ifTrue:[
+		self isUsingUnicode
+		    ifTrue: [ string := aString asUnicode16String  ]
+		    ifFalse:[ string := aString asSingleByteString ].
+	    ].
+	    string
+	].
+	resRemoteName  := checkAndGetString value:( aResourceOrNil remoteName ).
+	resLocalName   := checkAndGetString value:( aResourceOrNil localName ).
+	resComment     := checkAndGetString value:( aResourceOrNil comment ).
+	resProvider    := checkAndGetString value:( aResourceOrNil provider ).
     ].
     resourceHandle := self new.
 
@@ -17464,75 +17377,75 @@
 #endif
 
     if( resScope == nil ) {
-        __lpnetRes = 0;
+	__lpnetRes = 0;
     } else {
-        int __sz;
-
-        ZeroMemory( __buffer, (__cp - __buffer) );
-
-        __lpnetRes->dwScope       = __unsignedLongIntVal( resScope );
-        __lpnetRes->dwType        = __unsignedLongIntVal( resType  );
-        __lpnetRes->dwUsage       = __unsignedLongIntVal( resUsage );
-        __lpnetRes->dwDisplayType = __unsignedLongIntVal( resDisplayType );
-
-        if( resRemoteName != nil ) {
+	int __sz;
+
+	ZeroMemory( __buffer, (__cp - __buffer) );
+
+	__lpnetRes->dwScope       = __unsignedLongIntVal( resScope );
+	__lpnetRes->dwType        = __unsignedLongIntVal( resType  );
+	__lpnetRes->dwUsage       = __unsignedLongIntVal( resUsage );
+	__lpnetRes->dwDisplayType = __unsignedLongIntVal( resDisplayType );
+
+	if( resRemoteName != nil ) {
 #ifdef USE_ANSI_NETWORKRESOURCES
-            __sp = __stringVal(resRemoteName);
-            __sz = strlen(__sp);
-#else
-            __sp = __unicode16StringVal(resRemoteName);
-            __sz = __unicode16StringSize(resRemoteName);
-#endif
-            for( __lpnetRes->lpRemoteName = __cp; __sz > 0; --__sz ) { * __cp++ = * __sp++; }
-            *__cp++ = 0;
-        }
-
-        if( resLocalName != nil ) {
+	    __sp = __stringVal(resRemoteName);
+	    __sz = strlen(__sp);
+#else
+	    __sp = __unicode16StringVal(resRemoteName);
+	    __sz = __unicode16StringSize(resRemoteName);
+#endif
+	    for( __lpnetRes->lpRemoteName = __cp; __sz > 0; --__sz ) { * __cp++ = * __sp++; }
+	    *__cp++ = 0;
+	}
+
+	if( resLocalName != nil ) {
 #ifdef USE_ANSI_NETWORKRESOURCES
-            __sp = __stringVal(resLocalName);
-            __sz = strlen(__sp);
-#else
-            __sp = __unicode16StringVal(resLocalName);
-            __sz = __unicode16StringSize(resLocalName);
-#endif
-            for( __lpnetRes->lpLocalName = __cp; __sz > 0; --__sz ) { * __cp++ = * __sp++; }
-            *__cp++ = 0;
-        }
-
-        if( resComment != nil ) {
+	    __sp = __stringVal(resLocalName);
+	    __sz = strlen(__sp);
+#else
+	    __sp = __unicode16StringVal(resLocalName);
+	    __sz = __unicode16StringSize(resLocalName);
+#endif
+	    for( __lpnetRes->lpLocalName = __cp; __sz > 0; --__sz ) { * __cp++ = * __sp++; }
+	    *__cp++ = 0;
+	}
+
+	if( resComment != nil ) {
 #ifdef USE_ANSI_NETWORKRESOURCES
-            __sp = __stringVal(resComment);
-            __sz = strlen(__sp);
-#else
-            __sp = __unicode16StringVal(resComment);
-            __sz = __unicode16StringSize(resComment);
-#endif
-            for( __lpnetRes->lpComment = __cp; __sz > 0; --__sz ) { * __cp++ = * __sp++; }
-            *__cp++ = 0;
-        }
-
-        if( resProvider != nil ) {
+	    __sp = __stringVal(resComment);
+	    __sz = strlen(__sp);
+#else
+	    __sp = __unicode16StringVal(resComment);
+	    __sz = __unicode16StringSize(resComment);
+#endif
+	    for( __lpnetRes->lpComment = __cp; __sz > 0; --__sz ) { * __cp++ = * __sp++; }
+	    *__cp++ = 0;
+	}
+
+	if( resProvider != nil ) {
 #ifdef USE_ANSI_NETWORKRESOURCES
-            __sp = __stringVal(resProvider);
-            __sz = strlen(__sp);
-#else
-            __sp = __unicode16StringVal(resProvider);
-            __sz = __unicode16StringSize(resProvider);
-#endif
-            for( __lpnetRes->lpProvider = __cp; __sz > 0; --__sz ) { * __cp++ = * __sp++; }
-            *__cp++ = 0;
-        }
+	    __sp = __stringVal(resProvider);
+	    __sz = strlen(__sp);
+#else
+	    __sp = __unicode16StringVal(resProvider);
+	    __sz = __unicode16StringSize(resProvider);
+#endif
+	    for( __lpnetRes->lpProvider = __cp; __sz > 0; --__sz ) { * __cp++ = * __sp++; }
+	    *__cp++ = 0;
+	}
     }
 
 #ifdef DO_WRAP_CALLS
     do {
-        __threadErrno = 0;
+	__threadErrno = 0;
 #ifdef USE_ANSI_NETWORKRESOURCES
-        // do not cast to INT - will loose sign bit then!
-        __errno = (int)(STX_API_NOINT_CALL5( "WNetOpenEnumA",  WNetOpenEnumA,  __scope, __type, __usage, __lpnetRes, & __hEnum ));
-#else
-        // do not cast to INT - will loose sign bit then!
-        __errno = (int)(STX_API_NOINT_CALL5( "WNetOpenEnumW", WNetOpenEnumW, __scope, __type, __usage, __lpnetRes, & __hEnum ));
+	// do not cast to INT - will loose sign bit then!
+	__errno = (int)(STX_API_NOINT_CALL5( "WNetOpenEnumA",  WNetOpenEnumA,  __scope, __type, __usage, __lpnetRes, & __hEnum ));
+#else
+	// do not cast to INT - will loose sign bit then!
+	__errno = (int)(STX_API_NOINT_CALL5( "WNetOpenEnumW", WNetOpenEnumW, __scope, __type, __usage, __lpnetRes, & __hEnum ));
 #endif
     } while ((__errno < 0) && (__threadErrno == EINTR));
 #else
@@ -17546,16 +17459,16 @@
 #endif
 
     if( __errno == NO_ERROR ) {
-        __externalAddressVal(resourceHandle) = (void *) __hEnum;
+	__externalAddressVal(resourceHandle) = (void *) __hEnum;
     } else {
-        resourceHandle = nil;
-        errorNumber    = __mkSmallInteger( __errno );
+	resourceHandle = nil;
+	errorNumber    = __mkSmallInteger( __errno );
     }
 
 %}.
     resourceHandle isNil ifTrue:[
-        aBlock notNil ifTrue:[ aBlock value: errorNumber ].
-        ^ nil
+	aBlock notNil ifTrue:[ aBlock value: errorNumber ].
+	^ nil
     ].
     resourceHandle registerForFinalization.
     ^ resourceHandle
@@ -17595,61 +17508,61 @@
     HANDLE __hEnum = (HANDLE)(__externalAddressVal(self));
 
     if ((__hEnum == 0) || (__hEnum == INVALID_HANDLE_VALUE)) {
-        __externalAddressVal(self) = (HANDLE)0;
+	__externalAddressVal(self) = (HANDLE)0;
     } else {
-        DWORD           __entries = 1;
-        DWORD           __bufSize = 8192;
-        int             __errno;
+	DWORD           __entries = 1;
+	DWORD           __bufSize = 8192;
+	int             __errno;
 
 #ifdef USE_ANSI_NETWORKRESOURCES
-        char            __buffer[ 8192 ];
-        LPNETRESOURCE   __lpNetRes  = (LPNETRESOURCE)  __buffer;
-
-        ZeroMemory( __buffer, sizeof(NETRESOURCE) );
-        __errno = WNetEnumResourceA ( __hEnum , & __entries , __lpNetRes, & __bufSize );
-#else
-        wchar_t         __buffer[ 8192 ];
-        LPNETRESOURCEW  __lpNetRes  = (LPNETRESOURCEW) __buffer;
-
-        ZeroMemory( __buffer, sizeof(NETRESOURCEW) );
-        __errno = WNetEnumResourceW ( __hEnum , & __entries , __lpNetRes, & __bufSize );
-#endif
-
-        if( (__errno  == NO_ERROR) && (__entries == 1) ) {
-            scope       = __MKUINT( __lpNetRes->dwScope );
-            type        = __MKUINT( __lpNetRes->dwType );
-            usage       = __MKUINT( __lpNetRes->dwUsage );
-            displayType = __MKUINT( __lpNetRes->dwDisplayType );
+	char            __buffer[ 8192 ];
+	LPNETRESOURCE   __lpNetRes  = (LPNETRESOURCE)  __buffer;
+
+	ZeroMemory( __buffer, sizeof(NETRESOURCE) );
+	__errno = WNetEnumResourceA ( __hEnum , & __entries , __lpNetRes, & __bufSize );
+#else
+	wchar_t         __buffer[ 8192 ];
+	LPNETRESOURCEW  __lpNetRes  = (LPNETRESOURCEW) __buffer;
+
+	ZeroMemory( __buffer, sizeof(NETRESOURCEW) );
+	__errno = WNetEnumResourceW ( __hEnum , & __entries , __lpNetRes, & __bufSize );
+#endif
+
+	if( (__errno  == NO_ERROR) && (__entries == 1) ) {
+	    scope       = __MKUINT( __lpNetRes->dwScope );
+	    type        = __MKUINT( __lpNetRes->dwType );
+	    usage       = __MKUINT( __lpNetRes->dwUsage );
+	    displayType = __MKUINT( __lpNetRes->dwDisplayType );
 
 #ifdef USE_ANSI_NETWORKRESOURCES
-            if( __lpNetRes->lpRemoteName != 0 ) { remoteName =  __MKSTRING( __lpNetRes->lpRemoteName ); }
-            if( __lpNetRes->lpLocalName  != 0 ) { localName  =  __MKSTRING( __lpNetRes->lpLocalName ); }
-            if( __lpNetRes->lpComment    != 0 ) { comment    =  __MKSTRING( __lpNetRes->lpComment ); }
-            if( __lpNetRes->lpProvider   != 0 ) { provider   =  __MKSTRING( __lpNetRes->lpProvider ); }
-#else
-            if( __lpNetRes->lpRemoteName != 0 ) { remoteName =  __MKU16STRING( __lpNetRes->lpRemoteName ); }
-            if( __lpNetRes->lpLocalName  != 0 ) { localName  =  __MKU16STRING( __lpNetRes->lpLocalName ); }
-            if( __lpNetRes->lpComment    != 0 ) { comment    =  __MKU16STRING( __lpNetRes->lpComment ); }
-            if( __lpNetRes->lpProvider   != 0 ) { provider   =  __MKU16STRING( __lpNetRes->lpProvider ); }
-#endif
-        }
+	    if( __lpNetRes->lpRemoteName != 0 ) { remoteName =  __MKSTRING( __lpNetRes->lpRemoteName ); }
+	    if( __lpNetRes->lpLocalName  != 0 ) { localName  =  __MKSTRING( __lpNetRes->lpLocalName ); }
+	    if( __lpNetRes->lpComment    != 0 ) { comment    =  __MKSTRING( __lpNetRes->lpComment ); }
+	    if( __lpNetRes->lpProvider   != 0 ) { provider   =  __MKSTRING( __lpNetRes->lpProvider ); }
+#else
+	    if( __lpNetRes->lpRemoteName != 0 ) { remoteName =  __MKU16STRING( __lpNetRes->lpRemoteName ); }
+	    if( __lpNetRes->lpLocalName  != 0 ) { localName  =  __MKU16STRING( __lpNetRes->lpLocalName ); }
+	    if( __lpNetRes->lpComment    != 0 ) { comment    =  __MKU16STRING( __lpNetRes->lpComment ); }
+	    if( __lpNetRes->lpProvider   != 0 ) { provider   =  __MKU16STRING( __lpNetRes->lpProvider ); }
+#endif
+	}
     }
 %}.
     scope notNil ifTrue:[ |netResource|
-        netResource := NetworkResource new.
-
-        "map integer values to symbol excluding the usage..."
-        netResource scope: (self class scopeMappingTable at:scope ifAbsent:[scope]).
-        netResource type:  (self class typeMappingTable  at:type ifAbsent:[type]).
-        netResource displayType: (self class displayTypeMappingTable at:displayType ifAbsent:[displayType]).
-        netResource usage: usage.
-
-        netResource remoteName: remoteName.
-        netResource localName: localName.
-        netResource comment: comment.
-        netResource provider: provider.
-
-        ^ netResource
+	netResource := NetworkResource new.
+
+	"map integer values to symbol excluding the usage..."
+	netResource scope: (self class scopeMappingTable at:scope ifAbsent:[scope]).
+	netResource type:  (self class typeMappingTable  at:type ifAbsent:[type]).
+	netResource displayType: (self class displayTypeMappingTable at:displayType ifAbsent:[displayType]).
+	netResource usage: usage.
+
+	netResource remoteName: remoteName.
+	netResource localName: localName.
+	netResource comment: comment.
+	netResource provider: provider.
+
+	^ netResource
     ].
     self close.
     ^ nil
@@ -17665,8 +17578,8 @@
     HANDLE __hEnum = (HANDLE)(__externalAddressVal(self));
 
     if (__hEnum) {
-        __externalAddressVal(self) = (HANDLE)0;
-        WNetCloseEnum(__hEnum);
+	__externalAddressVal(self) = (HANDLE)0;
+	WNetCloseEnum(__hEnum);
     }
 %}.
 ! !
@@ -17743,28 +17656,28 @@
 
 scope
     "The scope of the enumeration
-        RESOURCE_CONNECTED RESOURCE_GLOBALNET RESOURCE_REMEMBERED
+	RESOURCE_CONNECTED RESOURCE_GLOBALNET RESOURCE_REMEMBERED
     "
     ^ scope
 !
 
 scope: theScope
     "The scope of the enumeration
-        RESOURCE_CONNECTED RESOURCE_GLOBALNET RESOURCE_REMEMBERED
+	RESOURCE_CONNECTED RESOURCE_GLOBALNET RESOURCE_REMEMBERED
     "
     scope := theScope.
 !
 
 type
     "describes the type of the resource
-        RESOURCETYPE_ANY  RESOURCETYPE_DISK  RESOURCETYPE_PRINT
+	RESOURCETYPE_ANY  RESOURCETYPE_DISK  RESOURCETYPE_PRINT
     "
     ^ type
 !
 
 type: theType
     "describes the type of the resource
-        RESOURCETYPE_ANY  RESOURCETYPE_DISK  RESOURCETYPE_PRINT
+	RESOURCETYPE_ANY  RESOURCETYPE_DISK  RESOURCETYPE_PRINT
     "
     type := theType.
 !
@@ -17789,20 +17702,20 @@
     | paction |
 
     paction := [: anIdentifier :theValue |
-        anIdentifier printOn: aStream.
-
-        theValue notNil ifTrue:[
-            theValue isInteger ifTrue:[
-                theValue printOn:aStream base:2 showRadix:true.
-            ] ifFalse:[
-                theValue isSymbol ifTrue:[
-                    theValue printOn: aStream.
-                ] ifFalse:[
-                    aStream nextPut: $". theValue printOn: aStream. aStream nextPut: $"
-                ]
-            ]
-        ].
-        aStream cr.
+	anIdentifier printOn: aStream.
+
+	theValue notNil ifTrue:[
+	    theValue isInteger ifTrue:[
+		theValue printOn:aStream base:2 showRadix:true.
+	    ] ifFalse:[
+		theValue isSymbol ifTrue:[
+		    theValue printOn: aStream.
+		] ifFalse:[
+		    aStream nextPut: $". theValue printOn: aStream. aStream nextPut: $"
+		]
+	    ]
+	].
+	aStream cr.
     ].
 
     aStream nextPutAll: 'NetworkResource {'; cr.
@@ -17835,7 +17748,7 @@
     DWORD __usage = __unsignedLongIntVal( flag );
 
     if( __usage & RESOURCEUSAGE_CONTAINER ) {
-        RETURN( true );
+	RETURN( true );
     }
 %}.
     ^ false
@@ -17845,7 +17758,7 @@
 
 closeHandle
     self address ~~ 0 ifTrue:[
-        OperatingSystem primClosePrinter:self.
+	OperatingSystem primClosePrinter:self.
     ]
 
     "Created: / 27-07-2006 / 14:48:37 / fm"
@@ -17880,9 +17793,9 @@
 !Win32OperatingSystem::Win32SerialPortHandle methodsFor:'opening'!
 
 open:portName baudRate:baudRate stopBitsType:stopBitsType
-                    parityType:parityType dataBits:dataBits
-                    inFlowCtrl:inFlowCtrlType outFlowCtrl:outFlowCtrlType
-                    xOnChar:xOnChar xOffChar:xOffChar
+		    parityType:parityType dataBits:dataBits
+		    inFlowCtrl:inFlowCtrlType outFlowCtrl:outFlowCtrlType
+		    xOnChar:xOnChar xOffChar:xOffChar
     "portName: COM%d
      baudRate: Integer
      stopBitsType: #stop1, #stop2 or #stop1_5
@@ -17901,13 +17814,13 @@
     DCB dcb;
     char *__portName;
     int __setBaudRate = 1,
-        __setDataBits = 1,
-        __setXOnChar = 1,
-        __setXOffChar = 1,
-        __setInFlowCtrl = 1,
-        __setOutFlowCtrl = 1,
-        __setStopBits = 1,
-        __setParityType = 1;
+	__setDataBits = 1,
+	__setXOnChar = 1,
+	__setXOffChar = 1,
+	__setInFlowCtrl = 1,
+	__setOutFlowCtrl = 1,
+	__setStopBits = 1,
+	__setParityType = 1;
     int __baudRate, __dataBits;
     int __xOnChar, __xOffChar;
     int __inFlowCtrl, __outFlowCtrl;
@@ -17922,90 +17835,90 @@
 #   define NONE      3
 
     if (__isStringLike(portName)) {
-        __portName = __stringVal(portName);
+	__portName = __stringVal(portName);
     } else {
-        goto failure;
+	goto failure;
     }
     if (__isSmallInteger(baudRate)) {
-        __baudRate = __intVal(baudRate);
+	__baudRate = __intVal(baudRate);
     } else if (baudRate == nil) {
-        __setBaudRate = 0;
+	__setBaudRate = 0;
     } else {
-        goto failure;
+	goto failure;
     }
 
     if (__isSmallInteger(dataBits)) {
-        __dataBits = __intVal(dataBits);
+	__dataBits = __intVal(dataBits);
     } else if (dataBits == nil) {
-        __setDataBits = 0;
+	__setDataBits = 0;
     } else {
-        goto failure;
+	goto failure;
     }
 
     if (__isSmallInteger(xOnChar)) {
-        __xOnChar = __intVal(xOnChar);
+	__xOnChar = __intVal(xOnChar);
     } else if (__isCharacter(xOnChar)) {
-        __xOnChar = __intVal(_characterVal(xOnChar));
+	__xOnChar = __intVal(_characterVal(xOnChar));
     } else if (xOnChar == nil) {
-        __setXOnChar = 0;
+	__setXOnChar = 0;
     } else {
-        goto failure;
+	goto failure;
     }
 
     if (__isSmallInteger(xOffChar)) {
-        __xOffChar = __intVal(xOffChar);
+	__xOffChar = __intVal(xOffChar);
     } else if (__isCharacter(xOffChar)) {
-        __xOffChar = __intVal(_characterVal(xOffChar));
+	__xOffChar = __intVal(_characterVal(xOffChar));
     } else if (xOffChar == nil) {
-        __setXOffChar = 0;
+	__setXOffChar = 0;
     } else {
-        goto failure;
+	goto failure;
     }
 
     if (inFlowCtrlType == @symbol(xOnOff)) {
-        __inFlowCtrl = XONOFF;
+	__inFlowCtrl = XONOFF;
     } else if (inFlowCtrlType == @symbol(hardware)) {
-        __inFlowCtrl = HARDWARE;
+	__inFlowCtrl = HARDWARE;
     } else if (inFlowCtrlType == nil) {
-        __setInFlowCtrl = 0;
+	__setInFlowCtrl = 0;
     } else {
-        goto failure;
+	goto failure;
     }
 
     if (outFlowCtrlType == @symbol(xOnOff)) {
-        __outFlowCtrl = XONOFF;
+	__outFlowCtrl = XONOFF;
     } else if (outFlowCtrlType == @symbol(hardware)) {
-        __outFlowCtrl = HARDWARE;
+	__outFlowCtrl = HARDWARE;
     } else if (outFlowCtrlType == nil) {
-        __setOutFlowCtrl = 0;
+	__setOutFlowCtrl = 0;
     } else {
-        goto failure;
+	goto failure;
     }
 
     if (stopBitsType == @symbol(stop1)) {
-        __stopBits = STOP1;
+	__stopBits = STOP1;
     } else if (stopBitsType == @symbol(stop2)) {
-        __stopBits = STOP2;
+	__stopBits = STOP2;
     } else if (stopBitsType == @symbol(stop1_5)) {
-        __stopBits = STOP1_5;
+	__stopBits = STOP1_5;
     } else if (stopBitsType == nil) {
-        __setStopBits = 0;
+	__setStopBits = 0;
     } else {
-        goto failure;
+	goto failure;
     }
 
     port = CreateFile(__portName,
-              GENERIC_READ | GENERIC_WRITE,
-              0,             /* comm devices must be opened with exclusive access */
-              NULL,          /* no security attrs */
-              OPEN_EXISTING, /* comm devices must use OPEN_EXISTING */
-              0,             /* no overlapped I/O */
-              NULL           /* hTemplate must be NULL for comm devices */
-           );
+	      GENERIC_READ | GENERIC_WRITE,
+	      0,             /* comm devices must be opened with exclusive access */
+	      NULL,          /* no security attrs */
+	      OPEN_EXISTING, /* comm devices must use OPEN_EXISTING */
+	      0,             /* no overlapped I/O */
+	      NULL           /* hTemplate must be NULL for comm devices */
+	   );
     if (port == INVALID_HANDLE_VALUE) {
-        console_fprintf(stderr, "Win32OS [info]: serial port open failed\n");
-        errorNumber = __mkSmallInteger( __WIN32_ERR(GetLastError()) );
-        goto failure;
+	console_fprintf(stderr, "Win32OS [info]: serial port open failed\n");
+	errorNumber = __mkSmallInteger( __WIN32_ERR(GetLastError()) );
+	goto failure;
     }
     /* Flush the driver */
     PurgeComm( port, PURGE_TXABORT | PURGE_RXABORT | PURGE_TXCLEAR | PURGE_RXCLEAR );
@@ -18032,42 +17945,42 @@
     if (__setXOffChar) dcb.XoffChar = __xOffChar;
 
     if (__setStopBits) {
-        /* set stop bits */
-        switch(__stopBits) {
-            case STOP1_5: dcb.StopBits = 1; break; /* 1.5 stop bits */
-            case STOP1: dcb.StopBits = 0; break; /* 1 stop bit */
-            case STOP2: dcb.StopBits = 2; break; /* 2 stop bits */
-            default: goto errExit;
-        }
+	/* set stop bits */
+	switch(__stopBits) {
+	    case STOP1_5: dcb.StopBits = 1; break; /* 1.5 stop bits */
+	    case STOP1: dcb.StopBits = 0; break; /* 1 stop bit */
+	    case STOP2: dcb.StopBits = 2; break; /* 2 stop bits */
+	    default: goto errExit;
+	}
     }
 
     if (__setParityType) {
-        /* set parity */
-        switch(__parityType) {
-            case NONE: dcb.Parity = NOPARITY; break;
-            case ODD: dcb.Parity = ODDPARITY; break;
-            case EVEN: dcb.Parity = EVENPARITY; break;
-            default: goto errExit;
-        }
+	/* set parity */
+	switch(__parityType) {
+	    case NONE: dcb.Parity = NOPARITY; break;
+	    case ODD: dcb.Parity = ODDPARITY; break;
+	    case EVEN: dcb.Parity = EVENPARITY; break;
+	    default: goto errExit;
+	}
     }
 
     if (__setInFlowCtrl) {
-        /* set control flow */
-        dcb.fInX = FALSE;
-        dcb.fDtrControl = FALSE;
-        if (__inFlowCtrl == XONOFF) dcb.fInX = TRUE;  /* XOn/XOff handshaking */
-        if (__inFlowCtrl == HARDWARE) dcb.fDtrControl = TRUE;  /* hardware handshaking */
+	/* set control flow */
+	dcb.fInX = FALSE;
+	dcb.fDtrControl = FALSE;
+	if (__inFlowCtrl == XONOFF) dcb.fInX = TRUE;  /* XOn/XOff handshaking */
+	if (__inFlowCtrl == HARDWARE) dcb.fDtrControl = TRUE;  /* hardware handshaking */
     }
     if (__setOutFlowCtrl) {
-        dcb.fOutX = FALSE;
-        dcb.fOutxCtsFlow = FALSE;
-
-        if (__outFlowCtrl == XONOFF) dcb.fOutX = TRUE;  /* XOn/XOff handshaking */
-        if (__outFlowCtrl == HARDWARE) dcb.fOutxCtsFlow = TRUE;  /* hardware handshaking */
+	dcb.fOutX = FALSE;
+	dcb.fOutxCtsFlow = FALSE;
+
+	if (__outFlowCtrl == XONOFF) dcb.fOutX = TRUE;  /* XOn/XOff handshaking */
+	if (__outFlowCtrl == HARDWARE) dcb.fOutxCtsFlow = TRUE;  /* hardware handshaking */
     }
 
     if (SetCommState(port, &dcb)) {
-        RETURN( true );
+	RETURN( true );
     }
 
     console_fprintf(stderr, "Win32OS [info]: serial port comm-setup failed\n");
@@ -18087,9 +18000,9 @@
 #   undef NONE
 %}.
     errorNumber isNil ifTrue:[
-        self error:'invalid argument(s)'.
+	self error:'invalid argument(s)'.
     ] ifFalse:[
-        (OperatingSystem errorHolderForNumber:errorNumber) reportError
+	(OperatingSystem errorHolderForNumber:errorNumber) reportError
     ].
 ! !
 
@@ -18102,9 +18015,9 @@
     HANDLE port = (HANDLE)(__externalAddressVal(self));
 
     if (port) {
-        __externalAddressVal(self) = (HANDLE)0;
-        PurgeComm( port, PURGE_TXABORT | PURGE_RXABORT | PURGE_TXCLEAR | PURGE_RXCLEAR );
-        CloseHandle(port);
+	__externalAddressVal(self) = (HANDLE)0;
+	PurgeComm( port, PURGE_TXABORT | PURGE_RXABORT | PURGE_TXCLEAR | PURGE_RXCLEAR );
+	CloseHandle(port);
     }
 %}.
 ! !
@@ -18117,18 +18030,18 @@
 
     if (port
      && __isSmallInteger(newRate)) {
-        DCB dcb;
-
-        ZeroMemory(&dcb, sizeof(dcb));
-        dcb.DCBlength = sizeof(dcb);
-        GetCommState(port, &dcb);
-
-        dcb.BaudRate = __intVal(newRate);
-
-        if (! SetCommState(port, &dcb)) {
-            RETURN(false);
-        }
-        RETURN(true);
+	DCB dcb;
+
+	ZeroMemory(&dcb, sizeof(dcb));
+	dcb.DCBlength = sizeof(dcb);
+	GetCommState(port, &dcb);
+
+	dcb.BaudRate = __intVal(newRate);
+
+	if (! SetCommState(port, &dcb)) {
+	    RETURN(false);
+	}
+	RETURN(true);
     }
 %}.
     self primitiveFailed.
@@ -18140,18 +18053,18 @@
 
     if (port
      && __isSmallInteger(newNumberOfBits)) {
-        DCB dcb;
-
-        ZeroMemory(&dcb, sizeof(dcb));
-        dcb.DCBlength = sizeof(dcb);
-        GetCommState(port, &dcb);
-
-        dcb.ByteSize = __intVal(newNumberOfBits);
-
-        if (! SetCommState(port, &dcb)) {
-            RETURN(false);
-        }
-        RETURN(true);
+	DCB dcb;
+
+	ZeroMemory(&dcb, sizeof(dcb));
+	dcb.DCBlength = sizeof(dcb);
+	GetCommState(port, &dcb);
+
+	dcb.ByteSize = __intVal(newNumberOfBits);
+
+	if (! SetCommState(port, &dcb)) {
+	    RETURN(false);
+	}
+	RETURN(true);
     }
 %}.
     self primitiveFailed.
@@ -18164,27 +18077,27 @@
     HANDLE port = (HANDLE)(__externalAddressVal(self));
 
     if (port) {
-        DCB dcb;
-
-        ZeroMemory(&dcb, sizeof(dcb));
-        dcb.DCBlength = sizeof(dcb);
-        GetCommState(port, &dcb);
-
-
-        if ((newParityTypeSymbol == nil) || (newParityTypeSymbol == @symbol(none))) {
-            dcb.Parity = NOPARITY;
-        } else if (newParityTypeSymbol == @symbol(odd)) {
-            dcb.Parity = ODDPARITY;
-        } else if (newParityTypeSymbol == @symbol(even)) {
-            dcb.Parity = EVENPARITY;
-        } else {
-            goto failure;
-        }
-
-        if (! SetCommState(port, &dcb)) {
-            RETURN(false);
-        }
-        RETURN(true);
+	DCB dcb;
+
+	ZeroMemory(&dcb, sizeof(dcb));
+	dcb.DCBlength = sizeof(dcb);
+	GetCommState(port, &dcb);
+
+
+	if ((newParityTypeSymbol == nil) || (newParityTypeSymbol == @symbol(none))) {
+	    dcb.Parity = NOPARITY;
+	} else if (newParityTypeSymbol == @symbol(odd)) {
+	    dcb.Parity = ODDPARITY;
+	} else if (newParityTypeSymbol == @symbol(even)) {
+	    dcb.Parity = EVENPARITY;
+	} else {
+	    goto failure;
+	}
+
+	if (! SetCommState(port, &dcb)) {
+	    RETURN(false);
+	}
+	RETURN(true);
     }
   failure: ;
 %}.
@@ -18197,26 +18110,26 @@
     HANDLE port = (HANDLE)(__externalAddressVal(self));
 
     if (port) {
-        DCB dcb;
-
-        ZeroMemory(&dcb, sizeof(dcb));
-        dcb.DCBlength = sizeof(dcb);
-        GetCommState(port, &dcb);
-
-        if (newStopBitsSymbol == @symbol(stop1)) {
-            dcb.Parity = 0 /* STOP1 */;
-        } else if (newStopBitsSymbol == @symbol(stop2)) {
-            dcb.Parity = 2 /* STOP2 */;
-        } else if (newStopBitsSymbol == @symbol(stop1_5)) {
-            dcb.Parity = 1 /* STOP1_5 */;
-        } else {
-            goto failure;
-        }
-
-        if (! SetCommState(port, &dcb)) {
-            RETURN(false);
-        }
-        RETURN(true);
+	DCB dcb;
+
+	ZeroMemory(&dcb, sizeof(dcb));
+	dcb.DCBlength = sizeof(dcb);
+	GetCommState(port, &dcb);
+
+	if (newStopBitsSymbol == @symbol(stop1)) {
+	    dcb.Parity = 0 /* STOP1 */;
+	} else if (newStopBitsSymbol == @symbol(stop2)) {
+	    dcb.Parity = 2 /* STOP2 */;
+	} else if (newStopBitsSymbol == @symbol(stop1_5)) {
+	    dcb.Parity = 1 /* STOP1_5 */;
+	} else {
+	    goto failure;
+	}
+
+	if (! SetCommState(port, &dcb)) {
+	    RETURN(false);
+	}
+	RETURN(true);
     }
   failure: ;
 %}.
@@ -18283,10 +18196,10 @@
     type := OperatingSystem socketTypeCodeOf:typeArg.
     proto := self protocolCodeOf:protoArg.
     serviceNameOrNil notNil ifTrue:[
-        serviceName := serviceNameOrNil printString.      "convert integer port numbers"
-        serviceNameOrNil isInteger ifTrue:[
-            port := serviceNameOrNil.
-        ].
+	serviceName := serviceNameOrNil printString.      "convert integer port numbers"
+	serviceNameOrNil isInteger ifTrue:[
+	    port := serviceNameOrNil.
+	].
     ]. "ifFalse:[serviceName := nil]"
 
 
@@ -18298,10 +18211,10 @@
      until we implement getAddrInfoW() for Borland C.
      If we really have 16-bit hostnames, this fails with #primitiveFailed"
     hostNameOrNil notNil ifTrue:[
-        hostName := hostNameOrNil asSingleByteStringIfPossible.
+	hostName := hostNameOrNil asSingleByteStringIfPossible.
     ].  "ifFalse:[hostName := nil] is nil anyway"
     serviceName notNil ifTrue:[
-        serviceName := serviceName asSingleByteStringIfPossible.
+	serviceName := serviceName asSingleByteStringIfPossible.
     ].
 %{
 #endif // !AI_NUMERICHOST
@@ -18316,30 +18229,30 @@
     int cnt = 0;
 
     if (hostName == nil) {
-        __hostName = 0;
+	__hostName = 0;
     } else if (__isStringLike(hostName)) {
-        strncpy(__hostNameCopy, __stringVal(hostName), sizeof(__hostNameCopy)-1);
-        __hostName = __hostNameCopy;
+	strncpy(__hostNameCopy, __stringVal(hostName), sizeof(__hostNameCopy)-1);
+	__hostName = __hostNameCopy;
     } else if (__isUnicode16String(hostName)) {
-        error = @symbol(unsupportedUnicodeName);
-        errorString = __MKSTRING("Unicode hostnames are not yet supported");
-        goto exitPrim;
+	error = @symbol(unsupportedUnicodeName);
+	errorString = __MKSTRING("Unicode hostnames are not yet supported");
+	goto exitPrim;
     } else {
-        error = @symbol(badArgument1);
-        goto exitPrim;
+	error = @symbol(badArgument1);
+	goto exitPrim;
     }
     if (serviceName == nil) {
-        __serviceName = 0;
+	__serviceName = 0;
     } else if (__isStringLike(serviceName)) {
-        strncpy(__serviceNameCopy, __stringVal(serviceName), sizeof(__serviceNameCopy)-1);
-        __serviceName = __serviceNameCopy;
+	strncpy(__serviceNameCopy, __stringVal(serviceName), sizeof(__serviceNameCopy)-1);
+	__serviceName = __serviceNameCopy;
     } 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;
     }
 
 {
@@ -18352,101 +18265,101 @@
 
     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 {
 # ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = (int)(STX_WSA_NOINT_CALL4( "getaddrinfo", getaddrinfo, __hostName, __serviceName, &hints, &info));
-        } while ((ret < 0) && (__threadErrno == EINTR));
+	do {
+	    __threadErrno = 0;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = (int)(STX_WSA_NOINT_CALL4( "getaddrinfo", getaddrinfo, __hostName, __serviceName, &hints, &info));
+	} while ((ret < 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 != 0 && __threadErrno == 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_MEMORY:
-            error = @symbol(allocationFailure);
-            break;
-        case EAI_FAIL:
-            error = @symbol(permanentFailure);
-            break;
-        case EAI_AGAIN:
-            error = @symbol(tryAgain);
-            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_MEMORY:
+	    error = @symbol(allocationFailure);
+	    break;
+	case EAI_FAIL:
+	    error = @symbol(permanentFailure);
+	    break;
+	case EAI_AGAIN:
+	    error = @symbol(tryAgain);
+	    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:
@@ -18463,133 +18376,133 @@
     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) {
-        int err;
-
-        do {
+	int err;
+
+	do {
 # if 0 && defined(DO_WRAP_CALLS)
-            /* This does not work - the structure is allocated in thread local storage */
-            hp = STX_WSA_NOINT_CALL1("gethostbyname", gethostbyname, __hostName);
-            if ((INT)hp < 0) hp = NULL;
+	    /* This does not work - the structure is allocated in thread local storage */
+	    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, but allocates it in thread local storage
-             */
-            // __BEGIN_INTERRUPTABLE__
-            hp = gethostbyname(__hostName);
-            // __END_INTERRUPTABLE__
-#endif
-        } while ((hp == NULL
-                  && (err = WSAGetLastError()) == EINTR));
-        if (hp == 0) {
-            switch (err) {
-            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(err);
-            goto err;
-        }
-
-        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;
+	    /* __BEGIN_INTERRUPTABLE__ is dangerous, because gethostbyname
+	     * uses a static data area, but allocates it in thread local storage
+	     */
+	    // __BEGIN_INTERRUPTABLE__
+	    hp = gethostbyname(__hostName);
+	    // __END_INTERRUPTABLE__
+#endif
+	} while ((hp == NULL
+		  && (err = WSAGetLastError()) == EINTR));
+	if (hp == 0) {
+	    switch (err) {
+	    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(err);
+	    goto err;
+	}
+
+	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(resp, type);
-        __ArrayInstPtr(resp)->a_element[3] = proto; __STORE(resp, 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{
-            if (__isSmallInteger(domain))
-                sa->sin_family = __intVal(domain);
-            else
-                sa->sin_family = AF_INET;
-            __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(resp, type);
+	__ArrayInstPtr(resp)->a_element[3] = proto; __STORE(resp, 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{
+	    if (__isSmallInteger(domain))
+		sa->sin_family = __intVal(domain);
+	    else
+		sa->sin_family = AF_INET;
+	    __ArrayInstPtr(resp)->a_element[1] = domain; __STORE(resp, domain);
+	}
     }
 
 err:;
@@ -18601,67 +18514,67 @@
 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:#AF_INET type:#stream protocol:nil flags:nil
+	    domain:#AF_INET type:#stream protocol:nil flags:nil
      self getAddressInfo:'localhost' serviceName:nil
-            domain:#AF_INET type:#stream protocol:#tcp flags:nil
+	    domain:#AF_INET type:#stream protocol:#tcp flags:nil
      self getAddressInfo:'localhost' serviceName:10
-            domain:#AF_INET type:#stream protocol:#tcp flags:nil
+	    domain:#AF_INET type:#stream protocol:#tcp flags:nil
      self getAddressInfo:'localhost' serviceName:'10'
-            domain:#AF_INET type:#stream protocol:#tcp flags:nil
+	    domain:#AF_INET type:#stream protocol:#tcp flags:nil
      self getAddressInfo:'blurb.exept.de' serviceName:nil
-            domain:#AF_INET type:nil protocol:nil flags:nil
+	    domain:#AF_INET type:nil protocol:nil flags:nil
      self getAddressInfo:'1.2.3.4' serviceName:'bla'
-            domain:#AF_INET type:nil protocol:nil flags:nil
+	    domain:#AF_INET type:nil protocol:nil flags:nil
      self getAddressInfo:'localhost' serviceName:'echo'
-            domain:#AF_INET type:nil protocol:nil flags:nil
+	    domain:#AF_INET type:nil protocol:nil flags:nil
      self getAddressInfo:nil serviceName:'echo'
-            domain:#AF_INET type:nil protocol:nil flags:nil
+	    domain:#AF_INET type:nil protocol:nil flags:nil
      self getAddressInfo:nil serviceName:nil
-            domain:#AF_INET type:nil protocol:nil flags:nil
+	    domain:#AF_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:'exeptn' serviceName:nil
-            domain:nil type:nil protocol:nil flags:nil
+	    domain:nil type:nil protocol:nil flags:nil
 
      self getAddressInfo:'localhost' asUnicode16String serviceName:nil
-            domain:nil type:nil protocol:nil flags:nil
+	    domain:nil type:nil protocol:nil flags:nil
      self getAddressInfo:'ützlbrützl' serviceName:nil
-            domain:nil type:nil protocol:nil flags:nil
+	    domain:nil type:nil protocol:nil flags:nil
      self getAddressInfo:'ützlbrützl' serviceName:nil
-            domain:nil type:nil protocol:nil flags:nil
+	    domain:nil type:nil protocol:nil flags:nil
      self getAddressInfo:'путин.ру' asUnicode16String serviceName:nil
-            domain:nil type:nil protocol:nil flags:nil
+	    domain:nil type:nil protocol:nil flags:nil
     "
 !
 
@@ -18705,20 +18618,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 == NULL && sp == NULL) {
-        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));
@@ -18726,185 +18639,185 @@
     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;
+	bp = (char *)(__byteArrayVal(socketAddress));
+	bp += nInstBytes;
 # ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = (int)(STX_WSA_NOINT_CALL7( "getnameinfo", getnameinfo, (struct sockaddr *)bp, (INT)sockAddrSize, hp, (INT)hsz, sp, (INT)ssz, (INT)__flags));
-        } while ((ret < 0) && (__threadErrno == EINTR));
+	do {
+	    __threadErrno = 0;
+	    // do not cast to INT - will loose sign bit then!
+	    ret = (int)(STX_WSA_NOINT_CALL7( "getnameinfo", getnameinfo, (struct sockaddr *)bp, (INT)sockAddrSize, hp, (INT)hsz, sp, (INT)ssz, (INT)__flags));
+	} while ((ret < 0) && (__threadErrno == EINTR));
 # else
-        __BEGIN_INTERRUPTABLE__
-        ret = getnameinfo((struct sockaddr *)bp, sockAddrSize,
-                          hp, hsz, sp, ssz, __flags);
-        __END_INTERRUPTABLE__
+	__BEGIN_INTERRUPTABLE__
+	ret = getnameinfo((struct sockaddr *)bp, sockAddrSize,
+			  hp, hsz, sp, ssz, __flags);
+	__END_INTERRUPTABLE__
 # endif
     } while (ret != 0 && __threadErrno == 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_MEMORY:
-                error = @symbol(allocationFailure);
-                break;
-            case EAI_FAIL:
-                error = @symbol(permanentFailure);
-                break;
-            case EAI_AGAIN:
-                error = @symbol(tryAgain);
-                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_MEMORY:
+		error = @symbol(allocationFailure);
+		break;
+	    case EAI_FAIL:
+		error = @symbol(permanentFailure);
+		break;
+	    case EAI_AGAIN:
+		error = @symbol(tryAgain);
+		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 (sa->sin_family == AF_INET6) {
-            if (sp)
-                serviceName = __MKSTRING(sp);
-            error = @symbol(AF_INET6);
-            goto err;
-        }
-
-        if (hp) {
-            struct hostent *hostp;
-            int err;
-
-            do {
-                /* must refetch in loop */
-                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)
-                      && ((err = WSAGetLastError()) == EINTR)
-            );
-            if (hostp == 0) {
-                switch (err) {
-                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(err);
-                goto err;
-            }
-            hp = hostp->h_name;
-        }
+	/*
+	 * 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 (sa->sin_family == AF_INET6) {
+	    if (sp)
+		serviceName = __MKSTRING(sp);
+	    error = @symbol(AF_INET6);
+	    goto err;
+	}
+
+	if (hp) {
+	    struct hostent *hostp;
+	    int err;
+
+	    do {
+		/* must refetch in loop */
+		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)
+		      && ((err = WSAGetLastError()) == EINTR)
+	    );
+	    if (hostp == 0) {
+		switch (err) {
+		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(err);
+		goto err;
+	    }
+	    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:[
-        (error == #AF_INET6 or:[errorString == #noAddress]) ifTrue:[
-            "This is a socket address of wrong size - probably an IPv6SocketAddres on a system where
-             the getNetByAddr() syscall is not supported"
-            ^ Array
-                with:socketAddress hostAddressString
-                with:serviceName.
-        ].
-        error isSymbol ifTrue:[
-            self primitiveFailed:error.
-        ].
-        ^ (HostAddressLookupError new
-                parameter:error;
-                messageText:' - ', (errorString ? error printString);
-                request:thisContext message) raiseRequest.
+	(error == #AF_INET6 or:[errorString == #noAddress]) ifTrue:[
+	    "This is a socket address of wrong size - probably an IPv6SocketAddres on a system where
+	     the getNetByAddr() syscall is not supported"
+	    ^ Array
+		with:socketAddress hostAddressString
+		with:serviceName.
+	].
+	error isSymbol ifTrue:[
+	    self primitiveFailed:error.
+	].
+	^ (HostAddressLookupError new
+		parameter:error;
+		messageText:' - ', (errorString ? error printString);
+		request:thisContext message) raiseRequest.
     ].
 
     ^ Array with:hostName with:serviceName
 
     "
      self getNameInfo:
-        (self getAddressInfo:'localhost' serviceName:'echo'
-                domain:#AF_INET type:#stream protocol:nil flags:nil) first socketAddress
-         wantHostName:true wantServiceName:true datagram:false flags:0
+	(self getAddressInfo:'localhost' serviceName:'echo'
+		domain:#AF_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:#AF_INET type:#stream protocol:nil flags:nil) first socketAddress
-         wantHostName:true wantServiceName:true datagram:false flags:0
+	(self getAddressInfo:'exept.exept.de' serviceName:'echo'
+		domain:#AF_INET type:#stream protocol:nil flags:nil) first socketAddress
+	 wantHostName:true wantServiceName:true datagram:false flags:0
 
      self getNameInfo:(IPSocketAddress hostAddress:#[1 2 3 4])
-         wantHostName:true wantServiceName:true datagram:false flags:0
+	 wantHostName:true wantServiceName:true datagram:false flags:0
 
      self getNameInfo:(IPv6SocketAddress localHost port:21)
-         wantHostName:true wantServiceName:true datagram:false flags:0
+	 wantHostName:true wantServiceName:true datagram:false flags:0
     "
 ! !
 
@@ -18912,7 +18825,7 @@
 
 initialize
 %{ /* NOCONTEXT */
-        __ExternalAddressInstPtr(self)->e_address = (void *)(INVALID_SOCKET);
+	__ExternalAddressInstPtr(self)->e_address = (void *)(INVALID_SOCKET);
 %}
 
     "
@@ -18948,8 +18861,8 @@
     SOCKET sock = (SOCKET)(__externalAddressVal(self));
 
     if (sock != INVALID_SOCKET) {
-        __externalAddressVal(self) = (void *)(INVALID_SOCKET);
-        closesocket(sock);
+	__externalAddressVal(self) = (void *)(INVALID_SOCKET);
+	closesocket(sock);
     }
 %}.
 ! !
@@ -18979,35 +18892,35 @@
 !Win32OperatingSystem::WinPointStructure methodsFor:'accessing'!
 
 asPoint
-        "Private - Answer the receiver as a Point."
+	"Private - Answer the receiver as a Point."
     ^self x @ self y
 
     "Created: / 03-08-2006 / 10:45:55 / fm"
 !
 
 x
-        "Private - Answer the x coordinate of the point."
+	"Private - Answer the x coordinate of the point."
     ^self longAt: 0 + 1
 
     "Created: / 03-08-2006 / 10:46:11 / fm"
 !
 
 x: anInteger
-        "Private - Set the x coordinate of the point."
+	"Private - Set the x coordinate of the point."
     self longAt: 0 + 1 put: anInteger
 
     "Created: / 03-08-2006 / 10:46:41 / fm"
 !
 
 y
-        "Private - Answer the y coordinate of the point."
+	"Private - Answer the y coordinate of the point."
     ^self longAt: 4 + 1
 
     "Created: / 03-08-2006 / 10:46:26 / fm"
 !
 
 y: anInteger
-        "Private - Set the y coordinate of the point."
+	"Private - Set the y coordinate of the point."
     self longAt: 4 + 1 put: anInteger
 
     "Created: / 03-08-2006 / 10:46:56 / fm"
@@ -19016,7 +18929,7 @@
 !Win32OperatingSystem::WinPointStructure methodsFor:'printing'!
 
 printOn: aStream
-        "Append a textual representation of the receiver to aStream."
+	"Append a textual representation of the receiver to aStream."
     aStream nextPutAll: self class name, ' { ', self asPoint printString, ' } '
 
     "Created: / 03-08-2006 / 10:45:40 / fm"