Fix bad variable name
authorStefan Vogel <sv@exept.de>
Thu, 21 Jun 2018 15:13:25 +0200
changeset 23124 d02eecc4b7b1
parent 23123 a120d0418bd7
child 23125 30c588bd215b
Fix bad variable name
ProjectDefinition.st
--- a/ProjectDefinition.st	Thu Jun 21 14:51:38 2018 +0200
+++ b/ProjectDefinition.st	Thu Jun 21 15:13:25 2018 +0200
@@ -2,7 +2,7 @@
 
 "
  COPYRIGHT (c) 2006 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
@@ -53,14 +53,14 @@
     You can define additional rules and flag settings for use in the makeFile generation:
 
     redefinable build-file attributes:
-        stcOptimizationOptions  -> STCLOCALOPT
-        stcWarningOptions       -> STCLOCALOPT
-        localIncludes_unix      -> LOCALINCLUDES (Make.proto)
-        localIncludes_win32     -> LOCALINCLUDES (bc.mak)
+	stcOptimizationOptions  -> STCLOCALOPT
+	stcWarningOptions       -> STCLOCALOPT
+	localIncludes_unix      -> LOCALINCLUDES (Make.proto)
+	localIncludes_win32     -> LOCALINCLUDES (bc.mak)
 
     for applications:
-        startupClassName
-        startupSelector
+	startupClassName
+	startupSelector
 
     for libraries:
 
@@ -70,7 +70,7 @@
 copyright
 "
  COPYRIGHT (c) 2006 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
@@ -84,38 +84,38 @@
 documentation
 "
     As ST/X is (still) very tightly bound with stc, we keep the package and project information
-    in a class-object (instead of some project object) and all queries about package contents and 
-    attributes are implemented as class methods. 
+    in a class-object (instead of some project object) and all queries about package contents and
+    attributes are implemented as class methods.
     (after all: a class is an object, which can be asked by sending it messages...
      ... so why would one want extra meta-descriptions with extra syntax?)
-    
+
     This has the advantage, that it can be compiled and included in a compiled class library just like any other class.
 
     Every package includes a subclass of me (an instance of my meta), which provides useful
-    information about the versioning and packaging. 
-    Me myself, I know how to generate dependency information and can generate makefiles and other build-support 
+    information about the versioning and packaging.
+    Me myself, I know how to generate dependency information and can generate makefiles and other build-support
     files for compilation (see the browser's 'Checkin Build Support File' menu item. For more details, see
     section 'Build Support Files' below).
 
     When a package is loaded from a binary shared class lib (i.e. a compiled class library is loaded
     via 'Smalltalk loadPackage:'), the loading is done in multiple phases:
-        1) the shared object is loaded, but not installed (registered) in Smalltalk
-        2) the ProjectDefinition class is registered and initialized.
-        3) the ProjectDefinition class is asked to load its prerequisites. 
-           This may recursively lead to other packages to be loaded 
-           - either as binary class libraries, as bytecode or from source; whichever is found.
-        4) the remaining classes and extensions of the package are registered
+	1) the shared object is loaded, but not installed (registered) in Smalltalk
+	2) the ProjectDefinition class is registered and initialized.
+	3) the ProjectDefinition class is asked to load its prerequisites.
+	   This may recursively lead to other packages to be loaded
+	   - either as binary class libraries, as bytecode or from source; whichever is found.
+	4) the remaining classes and extensions of the package are registered
 
     ## Some special notes about extension methods:
       if a package is loaded (Smalltalk loadPackage:'foo:bar/baz'), any already loaded package of which
       methods are overwritten by an extension method of the loaded package, the other package is asked to safe those
-      methods in its safe(ForOverwrittenMethods). 
+      methods in its safe(ForOverwrittenMethods).
       Thus, if the other package or any of its classes is asked
       to file itself out, it can do so using the safe (otherwise, you'd not be able to check the original class into
       its repository while it has an overriding extension loaded).
 
       Also, the information about which other package was in charge when a method is overwritten is recorded in
-      extensionOverwriteInfo. 
+      extensionOverwriteInfo.
       This is used to correctly reinstall any overwritten method, whenever a package is unloaded.
 
     ## Build Support Files
@@ -128,13 +128,13 @@
     Packages may add more files to this list by defining an (extension) method in project definition class
     and by annotating the method by <file:overwrite:> annotation:
 
-        * the first parameter is the file name to generate as String, relative to the package root. As directory
-          separator, use slash (as on UNIX), it will be automagically converted to platform's separator.
-        * The second parametrer (true or false) tells the SCM whether the file should be generated (and thus
-          overwritten) upon each commit (when true) or only the first time (when false). Important: see the 
-          remark below.
-        * The method itself should return file's contents a string. If it returns nil, then the file is *not*
-          generated at all.
+	* the first parameter is the file name to generate as String, relative to the package root. As directory
+	  separator, use slash (as on UNIX), it will be automagically converted to platform's separator.
+	* The second parametrer (true or false) tells the SCM whether the file should be generated (and thus
+	  overwritten) upon each commit (when true) or only the first time (when false). Important: see the
+	  remark below.
+	* The method itself should return file's contents a string. If it returns nil, then the file is *not*
+	  generated at all.
 
     For examples, see #generate_java_build_auto_dot_xml and #generate_java_build_dot_xml defined by STX:LIBJAVA.
 
@@ -148,7 +148,7 @@
 
     There are two ways to add additional rules to generated makefiles (Make.proto and bc.mak):
       1) overriding #additionalRules_make_dot_proto and/or #additionalRules_bc_dot_mak
-      2) adding a method annotated by <file:target:> or <file:target:extends:> 
+      2) adding a method annotated by <file:target:> or <file:target:extends:>
 
     ### Overriding #additionalRules* methods
 
@@ -167,24 +167,24 @@
     to call 'ant' whenever a package is built, add a method like:
 
     additionalRuleAnt_make_dot_proto
-        <file: 'Make.proto' target: 'ant' extends: 'pre_objs' >  
-
-        ^ '
-        java:
-                ant -f java/build.xml
-        '
+	<file: 'Make.proto' target: 'ant' extends: 'pre_objs' >
+
+	^ '
+	java:
+		ant -f java/build.xml
+	'
 
     The meaning annotation parameters is the following:
 
-        * file: <String> - name of the file in which to include
-          the rule. Currently only two values are valid:
-          'Make.proto' and 'bc.mak'.
-        * target: <String> - name of the target'
-        * extends: <String> - optional name of the target that this additional
-          rule extends. This means that the extending target (specified by target:
-          annotation parameter) is called as part of building of  the extended target
-          (i.e., the target specified by extends: annotation parameter). Not all targets
-          are extendible, see below.
+	* file: <String> - name of the file in which to include
+	  the rule. Currently only two values are valid:
+	  'Make.proto' and 'bc.mak'.
+	* target: <String> - name of the target'
+	* extends: <String> - optional name of the target that this additional
+	  rule extends. This means that the extending target (specified by target:
+	  annotation parameter) is called as part of building of  the extended target
+	  (i.e., the target specified by extends: annotation parameter). Not all targets
+	  are extendible, see below.
 
     Method annotated by these annotations should return - when executed - a string
     with exactly one rule. The rule name SHOULD match with the name in target: annotation
@@ -201,14 +201,14 @@
     #### Extendable targets
 
     Make.proto:
-        all
-        clean
-        ...more to be added...
+	all
+	clean
+	...more to be added...
 
     bc.mak
-        ALL
-        clean
-        ...more to be added...
+	ALL
+	clean
+	...more to be added...
 
 "
 ! !
@@ -241,33 +241,33 @@
     packageDefinitionClassName := self projectDefinitionClassNameForDefinitionOf:aPackageID.
     class := Smalltalk classNamed:packageDefinitionClassName.
     class isNil ifTrue:[
-        doCreateIfAbsent ifTrue:[
-            typeOrNil = GUIApplicationType ifTrue:[
-                class := ApplicationDefinition newForPackage:aPackageID.
-            ] ifFalse:[
-                typeOrNil = NonGUIApplicationType ifTrue:[
-                    class := ApplicationDefinition newForPackage:aPackageID.
-                ] ifFalse:[
-                    typeOrNil = FolderForSubApplicationsType ifTrue:[
-                        class := FolderForProjectsDefinition newForPackage:aPackageID.
-                    ] ifFalse:[
-                        class := LibraryDefinition newForPackage:aPackageID.
-                    ]
-                ]
-            ].
-            "setup before prerequisites are defined"
-            class setupForType:typeOrNil.
-            "/ look what is there and include it; is this ok ?
-            class compileDescriptionMethods
-        ].
+	doCreateIfAbsent ifTrue:[
+	    typeOrNil = GUIApplicationType ifTrue:[
+		class := ApplicationDefinition newForPackage:aPackageID.
+	    ] ifFalse:[
+		typeOrNil = NonGUIApplicationType ifTrue:[
+		    class := ApplicationDefinition newForPackage:aPackageID.
+		] ifFalse:[
+		    typeOrNil = FolderForSubApplicationsType ifTrue:[
+			class := FolderForProjectsDefinition newForPackage:aPackageID.
+		    ] ifFalse:[
+			class := LibraryDefinition newForPackage:aPackageID.
+		    ]
+		]
+	    ].
+	    "setup before prerequisites are defined"
+	    class setupForType:typeOrNil.
+	    "/ look what is there and include it; is this ok ?
+	    class compileDescriptionMethods
+	].
     ] ifFalse:[
-        typeOrNil notNil ifTrue:[
-            doCreateIfAbsent ifTrue:[
-                class projectType == typeOrNil ifFalse: [
-                    class setupForType:typeOrNil.
-                ]
-            ].
-        ].
+	typeOrNil notNil ifTrue:[
+	    doCreateIfAbsent ifTrue:[
+		class projectType == typeOrNil ifFalse: [
+		    class setupForType:typeOrNil.
+		]
+	    ].
+	].
     ].
     ^ class
 
@@ -277,9 +277,9 @@
 
 definitionClassForPackage:newProjectID projectType:typeOrNil createIfAbsent:createIfAbsent
     ^ (self definitionClassForType:typeOrNil)
-            definitionClassForPackage:newProjectID
-            createIfAbsent:createIfAbsent
-            projectType:typeOrNil
+	    definitionClassForPackage:newProjectID
+	    createIfAbsent:createIfAbsent
+	    projectType:typeOrNil
 
     "Created: / 23-08-2006 / 14:28:53 / cg"
 !
@@ -300,8 +300,8 @@
 
 newForPackage:packageID
     ^ self
-        newNamed:(self projectDefinitionClassNameForDefinitionOf:packageID)
-        package:packageID.
+	newNamed:(self projectDefinitionClassNameForDefinitionOf:packageID)
+	package:packageID.
 
     "Created: / 11-08-2006 / 14:27:19 / cg"
 !
@@ -314,11 +314,11 @@
     self assert:(self ~~ ProjectDefinition).  "ProjectDefinition is abstract"
 
     newClass := self
-                    subclass:(newName asSymbol)
-                    instanceVariableNames:''
-                    classVariableNames:''
-                    poolDictionaries:''
-                    category:(self defaultCategory).
+		    subclass:(newName asSymbol)
+		    instanceVariableNames:''
+		    classVariableNames:''
+		    poolDictionaries:''
+		    category:(self defaultCategory).
 
     newClass package:packageID asSymbol.
     ^ newClass
@@ -356,10 +356,10 @@
     |mgr versionMethod revString|
 
     (mgr := managerOrNil) isNil ifTrue:[
-        mgr := SourceCodeManagerUtilities sourceCodeManagerFor:self.
-        mgr isNil ifTrue:[
-            ^ nil
-        ].
+	mgr := SourceCodeManagerUtilities sourceCodeManagerFor:self.
+	mgr isNil ifTrue:[
+	    ^ nil
+	].
     ].
 
     versionMethod := mgr nameOfVersionMethodForExtensions.
@@ -367,7 +367,7 @@
 
     revString := self perform:(mgr nameOfVersionMethodForExtensions) ifNotUnderstood:nil.
     revString isNil ifTrue:[
-        ^ nil.
+	^ nil.
     ].
     ^ mgr revisionInfoFromString:revString.
 
@@ -396,7 +396,7 @@
     ^ (aProjectID copyReplaceAny:':/' with:$_)
 
     "
-     stx_goodies_refactoryBrowser_lint fullPackageNameFor:#stx_goodies_refactoryBrowser_lint  
+     stx_goodies_refactoryBrowser_lint fullPackageNameFor:#stx_goodies_refactoryBrowser_lint
     "
 !
 
@@ -492,8 +492,8 @@
     ^ (aProjectID subStrings:$:) last
 
     "
-        bosch_dapasx_datenbasis_Definition moduleDirectory
-        bosch_dapasx_parameter_system_Definition moduleDirectory
+	bosch_dapasx_datenbasis_Definition moduleDirectory
+	bosch_dapasx_parameter_system_Definition moduleDirectory
     "
 
     "Created: / 08-08-2006 / 20:25:39 / fm"
@@ -567,10 +567,10 @@
     down := (parts2 copyFrom:common size+1) asStringWith:'\'.
     up isEmpty ifTrue:[
        down isEmpty ifTrue:[^ '.'].
-        ^ down.
+	^ down.
     ].
     down isEmpty ifTrue:[
-        ^ up.
+	^ up.
     ].
     ^ up, '\', down
 
@@ -634,7 +634,7 @@
 !
 
 parentProject
-    "return the packageID of the parent project. 
+    "return the packageID of the parent project.
      That is the projectID of the package above in the folder hierarchy"
 
     ^ (self parentProjectFor: self package)
@@ -643,14 +643,14 @@
      bosch_dapasx_hw_schnittstellen_Definition parentProject
      DapasX_Datenbasis parentProject
 
-     stx_libbasic parentProject      
-     stx_goodies_refactoryBrowser_lint parentProject      
+     stx_libbasic parentProject
+     stx_goodies_refactoryBrowser_lint parentProject
     "
 !
 
 parentProjectFor: aProjectID
     "given a packageID symbol or string, return the packageID of the
-     parent project. 
+     parent project.
      That is the projectID of the package above in the folder hierarchy"
 
     |path|
@@ -663,15 +663,15 @@
     "
      bosch_dapasx_hw_schnittstellen parentProject
 
-     self parentProjectFor:'bosch:dapasx'    
-     self parentProjectFor:'bosch:dapasx/hw_schnittstellen'    
-     self parentProjectFor:'stx:goodies/refactoryBrowser/lint'                   
-     self parentProjectFor:'stx:goodies/svg'                   
-     self parentProjectFor:'stx:libbasic'                      
-     self parentProjectFor:'exept:expecco/application'         
-
-     self parentProjectFor:'stx'                   
-     self parentProjectFor:'exept'                   
+     self parentProjectFor:'bosch:dapasx'
+     self parentProjectFor:'bosch:dapasx/hw_schnittstellen'
+     self parentProjectFor:'stx:goodies/refactoryBrowser/lint'
+     self parentProjectFor:'stx:goodies/svg'
+     self parentProjectFor:'stx:libbasic'
+     self parentProjectFor:'exept:expecco/application'
+
+     self parentProjectFor:'stx'
+     self parentProjectFor:'exept'
     "
 !
 
@@ -701,15 +701,15 @@
     parts2 := toPackageID asCollectionOfSubstringsSeparatedByAny:':/'.
     common := parts1 commonPrefixWith:parts2.
     common notEmpty ifTrue:[
-        up := ((1 to:parts1 size - common size) collect:[:p | oneUp]) asStringWith:''.
-        down := (parts2 copyFrom:common size+1) asStringWith:pathSeparator.
-        (up isEmpty and:[down isEmpty]) ifTrue:[^ '.'].
-        ^ up , down
+	up := ((1 to:parts1 size - common size) collect:[:p | oneUp]) asStringWith:''.
+	down := (parts2 copyFrom:common size+1) asStringWith:pathSeparator.
+	(up isEmpty and:[down isEmpty]) ifTrue:[^ '.'].
+	^ up , down
     ].
 
     rel := (self topRelativePathToPackage:toPackageID withSeparator:pathSeparator).
     (rel startsWith:('stx', pathSeparator)) ifTrue:[
-        ^ '$(TOP)', (rel copyFrom:'stx/' size) "/ notice: the separator remains
+	^ '$(TOP)', (rel copyFrom:'stx/' size) "/ notice: the separator remains
     ].
 
     ^ '$(TOP)', pathSeparator, oneUp, rel.
@@ -729,13 +729,13 @@
     |rel|
 
     aPackageID asPackageId module = self package asPackageId module ifTrue:[
-        ^ self pathToPackage:aPackageID from:self package withSeparator:pathSeparator.
+	^ self pathToPackage:aPackageID from:self package withSeparator:pathSeparator.
     ].
     rel := self topRelativePathToPackage:aPackageID withSeparator:pathSeparator.
     (rel startsWith:('stx', pathSeparator)) ifTrue:[
-        ^ '$(TOP)', (rel copyFrom:'stx/' size).   "keep the separator"
+	^ '$(TOP)', (rel copyFrom:'stx/' size).   "keep the separator"
     ] ifFalse:[
-        ^ '$(TOP)', pathSeparator, '..', pathSeparator, rel
+	^ '$(TOP)', pathSeparator, '..', pathSeparator, rel
     ]
 
     "
@@ -759,8 +759,8 @@
     parts := aProjectID asCollectionOfSubstringsSeparatedByAny:':/'.
 
     parts first = 'stx' ifTrue:[
-        parts size == 1 ifTrue:[^ ''].
-        ^ (((2 to:parts size-1) collect:[:p | oneUp]) asStringWith:'') , '..'
+	parts size == 1 ifTrue:[^ ''].
+	^ (((2 to:parts size-1) collect:[:p | oneUp]) asStringWith:'') , '..'
     ].
 
     ^ ((parts collect:[:p | oneUp]) asStringWith:'') , 'stx'
@@ -801,7 +801,7 @@
 
     s := aPackageId asString copy replaceAny:' :/-' with:$_.
     (s endsWith:$_) ifTrue:[
-        s := s copyButLast:1
+	s := s copyButLast:1
     ].
     ^ s
 
@@ -818,7 +818,7 @@
     "answer true, if this project is completely loaded into the image"
 
     projectIsLoaded isNil ifTrue:[
-        projectIsLoaded := false.
+	projectIsLoaded := false.
     ].
     ^ projectIsLoaded
 
@@ -831,10 +831,10 @@
 projectIsLoaded:aBoolean
     projectIsLoaded := aBoolean.
     aBoolean ifTrue:[
-        "register myself as dependent - I want to get notified on method changes"
-        self class addDependent:self.
-        self postLoadAction.
-        self executeHooks: #postLoad.
+	"register myself as dependent - I want to get notified on method changes"
+	self class addDependent:self.
+	self postLoadAction.
+	self executeHooks: #postLoad.
     ].
 !
 
@@ -843,7 +843,7 @@
      These are offered in the browser's methodList menu as 'Tag as' items.
      Allowing convenient tagging for things like '<resource: EXPECCO_API>'.
      When redefined, a collection of useful tag-strings should be returned."
-     
+
     ^ #()
 
     "Created: / 15-02-2017 / 16:42:48 / cg"
@@ -903,14 +903,14 @@
 
     excluded := self excludedFromCoverage.
     excluded notEmptyOrNil ifTrue:[
-        mclass := aMethod mclass.
-        mselector := aMethod selector.
-        excluded do:[:eachSpecLine|
-            eachSpecLine isArray ifTrue:[
-                (eachSpecLine first = mclass name and:[eachSpecLine second == mselector]) ifTrue:[ ^ true ].
-            ].
-            eachSpecLine = mclass name ifTrue:[ ^ true ].                
-        ].
+	mclass := aMethod mclass.
+	mselector := aMethod selector.
+	excluded do:[:eachSpecLine|
+	    eachSpecLine isArray ifTrue:[
+		(eachSpecLine first = mclass name and:[eachSpecLine second == mselector]) ifTrue:[ ^ true ].
+	    ].
+	    eachSpecLine = mclass name ifTrue:[ ^ true ].
+	].
     ].
 
     ^ false
@@ -956,16 +956,16 @@
     newSpec := self classNamesAndAttributes copy.
 
     toExclude do:[:eachClassToExclude |
-        |className|
-        className := eachClassToExclude theNonMetaclass name.
-        (self allClassNames includes:className) ifTrue:[
-            |idx|
-
-            idx := newSpec findFirst:[:entry | entry = className or:[entry first = className]].
-            idx ~~ 0 ifTrue:[
-                newSpec := newSpec copyWithoutIndex:idx.
-            ].
-        ].
+	|className|
+	className := eachClassToExclude theNonMetaclass name.
+	(self allClassNames includes:className) ifTrue:[
+	    |idx|
+
+	    idx := newSpec findFirst:[:entry | entry = className or:[entry first = className]].
+	    idx ~~ 0 ifTrue:[
+		newSpec := newSpec copyWithoutIndex:idx.
+	    ].
+	].
     ].
     self classNamesAndAttributes:newSpec usingCompiler:compilerOrNil
 
@@ -984,10 +984,10 @@
     oldSpec := self extensionMethodNames.
 
     idx := (1 to:oldSpec size-1 by:2)
-                detect:[:i |
-                    ((oldSpec at:i) = className)
-                    and:[ (oldSpec at:i+1) = selector ]]
-                ifNone:[ ^ self ].
+		detect:[:i |
+		    ((oldSpec at:i) = className)
+		    and:[ (oldSpec at:i+1) = selector ]]
+		ifNone:[ ^ self ].
 
     "/ attention: there are two spec-elements per method
     newSpec := oldSpec copyWithoutIndex:idx toIndex:idx+1.
@@ -1010,21 +1010,21 @@
     extensionMethods := self extensionMethods.
 
     toRemove do:[:eachMethodToRemove |
-        |className selector idx|
-
-        (extensionMethods includes:eachMethodToRemove) ifTrue:[
-            className := eachMethodToRemove mclass name.
-            selector := eachMethodToRemove selector.
-            idx := (1 to:newSpec size-1 by:2)
-                        detect:[:i |
-                            ((newSpec at:i) = className)
-                            and:[ (newSpec at:i+1) = selector ]]
-                        ifNone:nil.
-            idx notNil ifTrue:[
-                "/ attention: there are two spec-elements per method
-                newSpec := newSpec removeFromIndex:idx toIndex:idx+1
-            ]
-        ].
+	|className selector idx|
+
+	(extensionMethods includes:eachMethodToRemove) ifTrue:[
+	    className := eachMethodToRemove mclass name.
+	    selector := eachMethodToRemove selector.
+	    idx := (1 to:newSpec size-1 by:2)
+			detect:[:i |
+			    ((newSpec at:i) = className)
+			    and:[ (newSpec at:i+1) = selector ]]
+			ifNone:nil.
+	    idx notNil ifTrue:[
+		"/ attention: there are two spec-elements per method
+		newSpec := newSpec removeFromIndex:idx toIndex:idx+1
+	    ]
+	].
     ].
 
     newCode := self extensionMethodNames_code_For:newSpec.
@@ -1044,23 +1044,23 @@
     newSpec := oldSpec copy.
 
     toInclude do:[:eachClassToInclude |
-        |className|
-
-        className := eachClassToInclude theNonMetaclass name.
-        (self compiled_classNames includes:className) ifFalse:[
-            | idx entry|
-
-            idx := oldSpec findFirst:[:entry | entry = className or:[entry first = className]].
-            idx == 0 ifTrue:[
-                newSpec := newSpec copyWith:(Array with:className)
-            ] ifFalse:[
-                entry := newSpec at:idx.
-                entry isArray ifTrue:[
-                    entry := entry copyWithout:#autoload
-                ].
-                newSpec at:idx put:entry
-            ].
-        ].
+	|className|
+
+	className := eachClassToInclude theNonMetaclass name.
+	(self compiled_classNames includes:className) ifFalse:[
+	    | idx entry|
+
+	    idx := oldSpec findFirst:[:entry | entry = className or:[entry first = className]].
+	    idx == 0 ifTrue:[
+		newSpec := newSpec copyWith:(Array with:className)
+	    ] ifFalse:[
+		entry := newSpec at:idx.
+		entry isArray ifTrue:[
+		    entry := entry copyWithout:#autoload
+		].
+		newSpec at:idx put:entry
+	    ].
+	].
     ].
 
     self classNamesAndAttributes:newSpec usingCompiler:compilerOrNil
@@ -1080,10 +1080,10 @@
     extensionMethods := self extensionMethods.
 
     toInclude do:[:eachMethodToInclude |
-        (extensionMethods includes:eachMethodToInclude) ifFalse:[
-            newSpec := newSpec copyWith:eachMethodToInclude mclass name.
-            newSpec := newSpec copyWith:eachMethodToInclude selector.
-        ].
+	(extensionMethods includes:eachMethodToInclude) ifFalse:[
+	    newSpec := newSpec copyWith:eachMethodToInclude mclass name.
+	    newSpec := newSpec copyWith:eachMethodToInclude selector.
+	].
     ].
 
     newCode := self extensionMethodNames_code_For:newSpec.
@@ -1101,25 +1101,25 @@
     newSpec := self classNamesAndAttributes copy.
 
     toMakeAutoloaded do:[:eachClassToMakeAutoloaded |
-        |className|
-
-        className := eachClassToMakeAutoloaded theNonMetaclass name.
-        (self autoloaded_classNames includes:className) ifFalse:[
-            |idx entry|
-
-            idx := newSpec findFirst:[:entry | entry = className or:[entry first = className]].
-            idx == 0 ifTrue:[
-                newSpec := newSpec copyWith:(Array with:className with:#autoload)
-            ] ifFalse:[
-                entry := newSpec at:idx.
-                entry isArray ifTrue:[
-                    entry := (entry copyWithout:#autoload) copyWith:#autoload.
-                ] ifFalse:[
-                    entry := Array with:entry with:#autoload
-                ].
-                newSpec at:idx put:entry.
-            ].
-        ].
+	|className|
+
+	className := eachClassToMakeAutoloaded theNonMetaclass name.
+	(self autoloaded_classNames includes:className) ifFalse:[
+	    |idx entry|
+
+	    idx := newSpec findFirst:[:entry | entry = className or:[entry first = className]].
+	    idx == 0 ifTrue:[
+		newSpec := newSpec copyWith:(Array with:className with:#autoload)
+	    ] ifFalse:[
+		entry := newSpec at:idx.
+		entry isArray ifTrue:[
+		    entry := (entry copyWithout:#autoload) copyWith:#autoload.
+		] ifFalse:[
+		    entry := Array with:entry with:#autoload
+		].
+		newSpec at:idx put:entry.
+	    ].
+	].
     ].
 
     self classNamesAndAttributes:newSpec usingCompiler:compilerOrNil
@@ -1134,18 +1134,18 @@
      otherwise, merge new items into the existing lists."
 
     Class packageQuerySignal
-        answer:self package
-        do:[
-            self
-                forEachContentsMethodsCodeToCompileDo:
-                    [:code :category |
-                        (compilerOrNil ? self theMetaclass compilerClass)
-                            compile:code
-                            forClass:self theMetaclass
-                            inCategory:category.
-                    ]
-                ignoreOldDefinition:doRegenerate
-        ].
+	answer:self package
+	do:[
+	    self
+		forEachContentsMethodsCodeToCompileDo:
+		    [:code :category |
+			(compilerOrNil ? self theMetaclass compilerClass)
+			    compile:code
+			    forClass:self theMetaclass
+			    inCategory:category.
+		    ]
+		ignoreOldDefinition:doRegenerate
+	].
 !
 
 updateExtensionMethodNamesUsingCompiler:compilerOrNil
@@ -1169,18 +1169,18 @@
      otherwise, merge new items into the existing lists."
 
     Class packageQuerySignal
-        answer:self package
-        do:[
-            self
-                forEachMethodsCodeToCompileDo:
-                    [:code :category |
-                        (compilerOrNil ? self theMetaclass compilerClass)
-                            compile:code
-                            forClass:self theMetaclass
-                            inCategory:category.
-                    ]
-                ignoreOldDefinition:doRegenerate
-        ].
+	answer:self package
+	do:[
+	    self
+		forEachMethodsCodeToCompileDo:
+		    [:code :category |
+			(compilerOrNil ? self theMetaclass compilerClass)
+			    compile:code
+			    forClass:self theMetaclass
+			    inCategory:category.
+		    ]
+		ignoreOldDefinition:doRegenerate
+	].
 ! !
 
 !ProjectDefinition class methodsFor:'accessing - tests'!
@@ -1201,25 +1201,25 @@
 
     suite := TestSuite named:self package.
     classes := self classes
-                select:[:each |
-                    [
-                    each isLoaded ifFalse:[each autoload].
-                    (each isTestCaseLike) and:[ each isAbstract not ]
-                    ] on: Autoload autoloadFailedSignal do:[
-                                'FAILED TO LOAD: ' infoPrint.
-                                each name infoPrintCR.
-                        false
-                    ]
-                ].
+		select:[:each |
+		    [
+		    each isLoaded ifFalse:[each autoload].
+		    (each isTestCaseLike) and:[ each isAbstract not ]
+		    ] on: Autoload autoloadFailedSignal do:[
+				'FAILED TO LOAD: ' infoPrint.
+				each name infoPrintCR.
+			false
+		    ]
+		].
 
     classes := classes asSortedCollection:[:a :b | a name <= b name ].
     classes do: [:eachClass |
-        | tests |
-
-        eachClass name infoPrintCR.
-        tests := eachClass suite tests.
-        tests := tests reject:[:test|self shouldExcludeTest: test].
-        suite addTests: tests
+	| tests |
+
+	eachClass name infoPrintCR.
+	tests := eachClass suite tests.
+	tests := tests reject:[:test|self shouldExcludeTest: test].
+	suite addTests: tests
     ].
     ^ suite
 
@@ -1232,13 +1232,13 @@
 
 initialize
     AccessLock isNil ifTrue:[
-        LibraryType := #Library.
-        GUIApplicationType := #'GUI-Application'.
-        NonGUIApplicationType := #'NonGUI-Application'.
-        FolderForSubApplicationsType := #'Folder for Subapplications'.
-        AccessLock := Semaphore forMutualExclusion name:'ProjectDefinition Lock'.
-        Verbose := false.
-        PackagesBeingLoaded := Set new.
+	LibraryType := #Library.
+	GUIApplicationType := #'GUI-Application'.
+	NonGUIApplicationType := #'NonGUI-Application'.
+	FolderForSubApplicationsType := #'Folder for Subapplications'.
+	AccessLock := Semaphore forMutualExclusion name:'ProjectDefinition Lock'.
+	Verbose := false.
+	PackagesBeingLoaded := Set new.
     ].
 
     "
@@ -1260,12 +1260,12 @@
     isStandAloneApp := Smalltalk isStandAloneApp.
 
     self allSubclassesDo:[:eachProjectDefinitionClass |
-        eachProjectDefinitionClass isAbstract ifFalse:[
-            isStandAloneApp ifFalse:[
-                eachProjectDefinitionClass installAutoloadedClasses.
-            ].
-            eachProjectDefinitionClass projectIsLoaded:true.
-        ]
+	eachProjectDefinitionClass isAbstract ifFalse:[
+	    isStandAloneApp ifFalse:[
+		eachProjectDefinitionClass installAutoloadedClasses.
+	    ].
+	    eachProjectDefinitionClass projectIsLoaded:true.
+	]
     ].
 
     "
@@ -1283,62 +1283,62 @@
     classesToFixClassFileName := OrderedCollection new.
 
     self autoloaded_classNames do:[:className |
-        |cls|
-
-        "/ 'install as autoloaded: ' errorPrint. className errorPrintCR.
-        (cls := Smalltalk classNamed:className) isNil ifTrue:[
-            Error handle:[:ex |
-                (self name,' [warning]: failed to install autoloaded: ',className) errorPrintCR.
-                (self name,' [info]: reason: ',ex description) errorPrintCR.
-                "/ thisContext fullPrintAll.
-            ] do:[
-                cls := Smalltalk
-                    installAutoloadedClassNamed:className
-                    category:'* as yet unknown category *'
-                    package:self package
-                    revision:nil
-            ].
-            cls notNil ifTrue:[
-                classesToFixClassFileName add:cls.
-            ].
-        ].
+	|cls|
+
+	"/ 'install as autoloaded: ' errorPrint. className errorPrintCR.
+	(cls := Smalltalk classNamed:className) isNil ifTrue:[
+	    Error handle:[:ex |
+		(self name,' [warning]: failed to install autoloaded: ',className) errorPrintCR.
+		(self name,' [info]: reason: ',ex description) errorPrintCR.
+		"/ thisContext fullPrintAll.
+	    ] do:[
+		cls := Smalltalk
+		    installAutoloadedClassNamed:className
+		    category:'* as yet unknown category *'
+		    package:self package
+		    revision:nil
+	    ].
+	    cls notNil ifTrue:[
+		classesToFixClassFileName add:cls.
+	    ].
+	].
     ].
 
     Smalltalk addStartBlock:[
-        |abbrevs|
-
-        abbrevs := self abbrevs.
-        "/ patch the classFileNames
-        classesToFixClassFileName do:[:cls |
-            |entry classFilenameFromAbbreviations|
-
-            entry := abbrevs at:cls name ifAbsent:nil.
-            entry notNil ifTrue:[
-                classFilenameFromAbbreviations := entry fileName.
-                classFilenameFromAbbreviations notNil ifTrue:[
-                    classFilenameFromAbbreviations := classFilenameFromAbbreviations,'.st'.
-                    (classFilenameFromAbbreviations ~= cls getClassFilename) ifTrue:[
-                        cls setClassFilename:classFilenameFromAbbreviations
-                    ].
-                ].
-            ]
-        ].
-
-        "/ patch the categories
-        Class withoutUpdatingChangesDo:[
-            |entry|
-
-            self classNames do:[:nm |
-                |cls|
-
-                ((cls := Smalltalk at: nm) notNil
-                        and:[ cls isLoaded not
-                        and:[ (entry := abbrevs at:cls name ifAbsent:[nil]) notNil
-                ]]) ifTrue:[
-                    cls category: (entry category)
-                ]
-            ]
-        ]
+	|abbrevs|
+
+	abbrevs := self abbrevs.
+	"/ patch the classFileNames
+	classesToFixClassFileName do:[:cls |
+	    |entry classFilenameFromAbbreviations|
+
+	    entry := abbrevs at:cls name ifAbsent:nil.
+	    entry notNil ifTrue:[
+		classFilenameFromAbbreviations := entry fileName.
+		classFilenameFromAbbreviations notNil ifTrue:[
+		    classFilenameFromAbbreviations := classFilenameFromAbbreviations,'.st'.
+		    (classFilenameFromAbbreviations ~= cls getClassFilename) ifTrue:[
+			cls setClassFilename:classFilenameFromAbbreviations
+		    ].
+		].
+	    ]
+	].
+
+	"/ patch the categories
+	Class withoutUpdatingChangesDo:[
+	    |entry|
+
+	    self classNames do:[:nm |
+		|cls|
+
+		((cls := Smalltalk at: nm) notNil
+			and:[ cls isLoaded not
+			and:[ (entry := abbrevs at:cls name ifAbsent:[nil]) notNil
+		]]) ifTrue:[
+		    cls category: (entry category)
+		]
+	    ]
+	]
     ].
 
 
@@ -1357,12 +1357,12 @@
 
 applicationIconFileNameLinux_code
     ^ String streamContents:[:s |
-        s nextPutLine:'applicationIconFileNameLinux'.
-        s nextPutLine:'    "Return the name (without suffix) of an icon-file (the app''s icon).'.
-        s nextPutLine:'     This is currently unused (will be for desktop definitions)"'.
-        s cr;
-        nextPutLine:'    ^ nil';
-        nextPutLine:'    " ^ self applicationName "'.
+	s nextPutLine:'applicationIconFileNameLinux'.
+	s nextPutLine:'    "Return the name (without suffix) of an icon-file (the app''s icon).'.
+	s nextPutLine:'     This is currently unused (will be for desktop definitions)"'.
+	s cr;
+	nextPutLine:'    ^ nil';
+	nextPutLine:'    " ^ self applicationName "'.
     ].
 
     "
@@ -1375,12 +1375,12 @@
 
 applicationIconFileNameOSX_code
     ^ String streamContents:[:s |
-        s nextPutLine:'applicationIconFileNameOSX'.
-        s nextPutLine:'    "Return the name (without suffix) of an icon-file (the app''s icon).'.
-        s nextPutLine:'     This is used to create the osx/Info.plist file"'.
-        s cr;
-        nextPutLine:'    ^ nil';
-        nextPutLine:'    " ^ self applicationName "'.
+	s nextPutLine:'applicationIconFileNameOSX'.
+	s nextPutLine:'    "Return the name (without suffix) of an icon-file (the app''s icon).'.
+	s nextPutLine:'     This is used to create the osx/Info.plist file"'.
+	s cr;
+	nextPutLine:'    ^ nil';
+	nextPutLine:'    " ^ self applicationName "'.
     ].
 
     "
@@ -1394,12 +1394,12 @@
 
 applicationIconFileNameWindows_code
     ^ String streamContents:[:s |
-        s nextPutLine:'applicationIconFileNameWindows'.
-        s nextPutLine:'    "Return the name (without suffix) of an icon-file (the app''s icon).'.
-        s nextPutLine:'     This will be included in the rc-resource file for Windowsdeployment"'.
-        s cr;
-        nextPutLine:'    ^ nil';
-        nextPutLine:'    " ^ self applicationName "'.
+	s nextPutLine:'applicationIconFileNameWindows'.
+	s nextPutLine:'    "Return the name (without suffix) of an icon-file (the app''s icon).'.
+	s nextPutLine:'     This will be included in the rc-resource file for Windowsdeployment"'.
+	s cr;
+	nextPutLine:'    ^ nil';
+	nextPutLine:'    " ^ self applicationName "'.
     ].
 
     "
@@ -1412,14 +1412,14 @@
 
 applicationIconFileName_code
     "obsolete - replaced by three separate methods as-per-OS"
-    
+
     ^ String streamContents:[:s |
-        s nextPutLine:'applicationIconFileName'.
-        s nextPutLine:'    "Return the name (without suffix) of an icon-file (the app''s icon);'.
-        s nextPutLine:'    "will be included in the rc-resource file"'.
-        s cr;
-        nextPutLine:'    ^ nil';
-        nextPutLine:'    " ^ self applicationName "'.
+	s nextPutLine:'applicationIconFileName'.
+	s nextPutLine:'    "Return the name (without suffix) of an icon-file (the app''s icon);'.
+	s nextPutLine:'    "will be included in the rc-resource file"'.
+	s cr;
+	nextPutLine:'    ^ nil';
+	nextPutLine:'    " ^ self applicationName "'.
     ].
 
     "
@@ -1434,21 +1434,21 @@
     "generate method code returning all classes of the project from the given spec."
 
     ^ String streamContents:[:s |
-        s nextPutLine:'classNamesAndAttributes'.
-        s nextPutLine:'    "lists the classes which are to be included in the project.'.
-        s nextPutLine:'     Each entry in the list may be: a single class-name (symbol),'.
-        s nextPutLine:'     or an array-literal consisting of class name and attributes.'.
-        s nextPutLine:'     Attributes are: #autoload or #<os> where os is one of win32, unix,..."'.
-        s nextPutLine:''.
-        s nextPutLine:'    ^ #('.
-        s nextPutLine:'        "<className> or (<className> attributes...) in load order"'.
-
-        (self classNamesAndAttributesFromSpecArray:aSpecArray) do:[:entry |
-            s spaces:8.
-            entry storeArrayElementOn:s.
-            s cr.
-        ].
-        s nextPutLine:'    )'
+	s nextPutLine:'classNamesAndAttributes'.
+	s nextPutLine:'    "lists the classes which are to be included in the project.'.
+	s nextPutLine:'     Each entry in the list may be: a single class-name (symbol),'.
+	s nextPutLine:'     or an array-literal consisting of class name and attributes.'.
+	s nextPutLine:'     Attributes are: #autoload or #<os> where os is one of win32, unix,..."'.
+	s nextPutLine:''.
+	s nextPutLine:'    ^ #('.
+	s nextPutLine:'        "<className> or (<className> attributes...) in load order"'.
+
+	(self classNamesAndAttributesFromSpecArray:aSpecArray) do:[:entry |
+	    s spaces:8.
+	    entry storeArrayElementOn:s.
+	    s cr.
+	].
+	s nextPutLine:'    )'
     ].
 
     "
@@ -1476,77 +1476,77 @@
     newSpec := OrderedCollection new.
 
     ignoreOldEntries ifFalse:[
-        oldSpec do:[:oldEntry |
-            |newEntry className cls |
-
-            newEntry := oldEntry copy.
-            className := newEntry first.
-
-            (ignored includes:className) ifFalse:[
-                cls := Smalltalk classNamed:className.
-                cls notNil ifTrue:[
-                    ignoreOldDefinition ifTrue:[
-                        cls isLoaded ifFalse:[
-                            (newEntry includes:#autoload) ifFalse:[
-                                newEntry := newEntry copyWith:#autoload.
-                            ].
-                        ].
-                    ].
-                    "JV @ 2010-06-19
-                     Force merge default class attributes with existing ones"
-                    newEntry := self mergeDefaultClassAttributesFor: cls with: newEntry.
-                    newSpec add:newEntry.   
-                ]
-            ].
-        ].
+	oldSpec do:[:oldEntry |
+	    |newEntry className cls |
+
+	    newEntry := oldEntry copy.
+	    className := newEntry first.
+
+	    (ignored includes:className) ifFalse:[
+		cls := Smalltalk classNamed:className.
+		cls notNil ifTrue:[
+		    ignoreOldDefinition ifTrue:[
+			cls isLoaded ifFalse:[
+			    (newEntry includes:#autoload) ifFalse:[
+				newEntry := newEntry copyWith:#autoload.
+			    ].
+			].
+		    ].
+		    "JV @ 2010-06-19
+		     Force merge default class attributes with existing ones"
+		    newEntry := self mergeDefaultClassAttributesFor: cls with: newEntry.
+		    newSpec add:newEntry.
+		]
+	    ].
+	].
     ].
     self searchForClasses do:[:eachClass |
-        |className attributes oldSpecEntry oldAttributes newEntry|
-
-        eachClass isJavaClass ifFalse:[
-            className := eachClass name.
-            (ignored includes:className) ifFalse:[
-                oldSpecEntry := oldSpec detect:[:entry | entry first = className] ifNone:nil.
-
-                (ignoreOldEntries or:[oldSpecEntry isNil]) ifTrue:[
-                    (eachClass isLoaded not or:[eachClass isPrivate not]) ifTrue:[
-                        (self additionalClassNamesAndAttributes includes:className) ifFalse:[
-                            (oldSpecEntry size > 1) ifTrue:[
-                                oldAttributes := oldSpecEntry copyFrom:2.
-                            ].
-
-                            ignoreOldDefinition ifTrue:[
-                                "take autoload attribute from classes state in the image"
-                                oldAttributes notNil ifTrue:[
-                                    attributes := oldAttributes copyWithout:#autoload.
-                                ] ifFalse:[
-                                    attributes := #()
-                                ].
-                                eachClass isLoaded ifFalse:[
-                                    attributes := attributes copyWith:#autoload.
-                                ].
-                            ] ifFalse:[
-                                "keep any existing attribute"
-                                oldAttributes notNil ifTrue:[
-                                    attributes := oldAttributes.
-                                ] ifFalse:[
-                                    attributes := eachClass isLoaded ifTrue:[ #() ] ifFalse:[ #(autoload) ].
-                                ].
-                            ].
-                            "JV @ 2010-06-19
-                             Support for additional class attributes and programming language attribute"
-                            attributes := self mergeDefaultClassAttributesFor: eachClass with: attributes.
-
-                            newEntry := Array with:className.
-                            attributes notEmptyOrNil ifTrue:[
-                                newEntry := newEntry , attributes.
-                            ].
-                            newSpec add:newEntry.   
-                        ]
-                    ]
-                ]
-            ]
-        ]
+	|className attributes oldSpecEntry oldAttributes newEntry|
+
+	eachClass isJavaClass ifFalse:[
+	    className := eachClass name.
+	    (ignored includes:className) ifFalse:[
+		oldSpecEntry := oldSpec detect:[:entry | entry first = className] ifNone:nil.
+
+		(ignoreOldEntries or:[oldSpecEntry isNil]) ifTrue:[
+		    (eachClass isLoaded not or:[eachClass isPrivate not]) ifTrue:[
+			(self additionalClassNamesAndAttributes includes:className) ifFalse:[
+			    (oldSpecEntry size > 1) ifTrue:[
+				oldAttributes := oldSpecEntry copyFrom:2.
+			    ].
+
+			    ignoreOldDefinition ifTrue:[
+				"take autoload attribute from classes state in the image"
+				oldAttributes notNil ifTrue:[
+				    attributes := oldAttributes copyWithout:#autoload.
+				] ifFalse:[
+				    attributes := #()
+				].
+				eachClass isLoaded ifFalse:[
+				    attributes := attributes copyWith:#autoload.
+				].
+			    ] ifFalse:[
+				"keep any existing attribute"
+				oldAttributes notNil ifTrue:[
+				    attributes := oldAttributes.
+				] ifFalse:[
+				    attributes := eachClass isLoaded ifTrue:[ #() ] ifFalse:[ #(autoload) ].
+				].
+			    ].
+			    "JV @ 2010-06-19
+			     Support for additional class attributes and programming language attribute"
+			    attributes := self mergeDefaultClassAttributesFor: eachClass with: attributes.
+
+			    newEntry := Array with:className.
+			    attributes notEmptyOrNil ifTrue:[
+				newEntry := newEntry , attributes.
+			    ].
+			    newSpec add:newEntry.
+			]
+		    ]
+		]
+	    ]
+	]
     ].
     ^ self classNamesAndAttributes_codeFor:newSpec
 
@@ -1579,9 +1579,9 @@
     "generate code that answers aString as the company name."
 
     ^ String streamContents:[:s |
-        s nextPutLine:'companyName'.
-        s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #companyName) comment; nextPutLine:'"'.
-        s cr; nextPutLine:'    ^ ',aString storeString.
+	s nextPutLine:'companyName'.
+	s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #companyName) comment; nextPutLine:'"'.
+	s cr; nextPutLine:'    ^ ',aString storeString.
     ].
 
     "
@@ -1595,13 +1595,13 @@
 
 compileDescriptionMethods
     (self isAbstract) ifTrue:[
-        self error:'I am abstract - must be a subclass of Libray- or ApplicationDefinition.'
+	self error:'I am abstract - must be a subclass of Libray- or ApplicationDefinition.'
     ].
 
     self
-        forEachMethodsCodeToCompileDo:[:code :category |
-            self compile:code categorized:category
-        ].
+	forEachMethodsCodeToCompileDo:[:code :category |
+	    self compile:code categorized:category
+	].
 
 "/    self instAndClassMethodsDo:[:m | m package:self package].
 
@@ -1618,9 +1618,9 @@
 
 description_code
     ^ String streamContents:[:s |
-        s nextPutLine:'description'.
-        s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #description) comment; nextPutLine:'"'.
-        s cr; nextPutLine:'    ^ ',self description asString storeString.
+	s nextPutLine:'description'.
+	s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #description) comment; nextPutLine:'"'.
+	s cr; nextPutLine:'    ^ ',self description asString storeString.
     ].
 
     "
@@ -1648,24 +1648,24 @@
     |subProjects|
 
     subProjects := (self subProjects, self includedInSubProjects) collect:[:eachLine|
-                        eachLine isString ifTrue:[
-                            eachLine
-                        ] ifFalse:[eachLine second = osSymbol ifTrue:[
-                            eachLine first.
-                        ] ifFalse:[
-                            nil.
-                        ]].
-                   ] as:OrderedSet.
+			eachLine isString ifTrue:[
+			    eachLine
+			] ifFalse:[eachLine second = osSymbol ifTrue:[
+			    eachLine first.
+			] ifFalse:[
+			    nil.
+			]].
+		   ] as:OrderedSet.
 
     subProjects remove:self package ifAbsent:[].
     subProjects remove:nil ifAbsent:[].
 
     self excludedFromSubProjects do:[:eachLine|
-        eachLine isString ifTrue:[
-            subProjects remove:eachLine ifAbsent:[]. 
-        ] ifFalse:[eachLine second = osSymbol ifTrue:[
-            subProjects remove:eachLine first ifAbsent:[].
-        ]].
+	eachLine isString ifTrue:[
+	    subProjects remove:eachLine ifAbsent:[].
+	] ifFalse:[eachLine second = osSymbol ifTrue:[
+	    subProjects remove:eachLine first ifAbsent:[].
+	]].
     ].
 
     ^ subProjects
@@ -1677,11 +1677,11 @@
     "generate the code of the #excludedFromPreRequisites method"
 
     ^ String streamContents:[:s |
-        s nextPutLine:'excludedFromPreRequisites'.
-        s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #excludedFromPreRequisites) comment; nextPutLine:'"'.
-        s nextPutLine:''.
-        s nextPutLine:'    ^ #('.
-        s nextPutLine:'    )'
+	s nextPutLine:'excludedFromPreRequisites'.
+	s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #excludedFromPreRequisites) comment; nextPutLine:'"'.
+	s nextPutLine:''.
+	s nextPutLine:'    ^ #('.
+	s nextPutLine:'    )'
     ].
 
     "Modified: / 05-03-2014 / 17:00:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1700,85 +1700,85 @@
 
 extensionMethodNames_code_For:extensionMethodNames
     ^ String streamContents:[:s |
-        |spec|
-
-        s nextPutLine:'extensionMethodNames'.
-        s nextPutLine:'    "lists the extension methods which are to be included in the project.'.
-        s nextPutLine:'     Entries are pairwise elements, consisting of class-name and selector."'.
-        s nextPutLine:''.
-        s nextPutLine:'    ^ #('.
-
-        spec := extensionMethodNames pairWiseCollect:[:className :selector | className -> selector ].
-        spec do:[:entry |
-            |mclassName mselector|
-
-            mclassName := entry key asSymbol.
-            (mclassName endsWith:' class') ifTrue:[
-                mclassName := mclassName asString.
-            ].
-            mselector := entry value asSymbol.
-
-            s spaces:8.
-            mclassName storeArrayElementOn:s.
-            s space.
-            mselector storeArrayElementOn:s.
-            s cr.
-        ].
-        s nextPutLine:'    )'
+	|spec|
+
+	s nextPutLine:'extensionMethodNames'.
+	s nextPutLine:'    "lists the extension methods which are to be included in the project.'.
+	s nextPutLine:'     Entries are pairwise elements, consisting of class-name and selector."'.
+	s nextPutLine:''.
+	s nextPutLine:'    ^ #('.
+
+	spec := extensionMethodNames pairWiseCollect:[:className :selector | className -> selector ].
+	spec do:[:entry |
+	    |mclassName mselector|
+
+	    mclassName := entry key asSymbol.
+	    (mclassName endsWith:' class') ifTrue:[
+		mclassName := mclassName asString.
+	    ].
+	    mselector := entry value asSymbol.
+
+	    s spaces:8.
+	    mclassName storeArrayElementOn:s.
+	    s space.
+	    mselector storeArrayElementOn:s.
+	    s cr.
+	].
+	s nextPutLine:'    )'
     ].
 !
 
 extensionMethodNames_code_ignoreOldEntries:ignoreOldEntries
     ^ String streamContents:[:s |
-        |oldSpec|
-
-        s nextPutLine:'extensionMethodNames'.
-        s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #extensionMethodNames) comment; nextPutLine:'"'.
-        s nextPutLine:''.
-        s nextPutLine:'    ^ #('.
-
-        oldSpec := self extensionMethodNames pairWiseCollect:[:className :selector | className -> selector ].
-
-        ignoreOldEntries ifFalse:[
-            oldSpec do:[:entry |
-                |mclassName mselector|
-
-                mclassName := entry key asSymbol.
-                (mclassName endsWith:' class') ifTrue:[
-                    mclassName := mclassName asString.
-                ].
-                mselector := entry value asSymbol.
-
-                s spaces:8.
-                mclassName storeArrayElementOn:s.
-                s space.
-                mselector storeArrayElementOn:s.
-                s cr.
-            ].
-        ].
-
-        self searchForExtensions do:[:eachMethod |
-            |attributes oldSpecEntry mclassName mselector|
-
-            mclassName := eachMethod mclass name.
-            mselector := eachMethod selector.
-            "JV@2012-09-07: Do not list Java methods in extensionMethodNames.
-             They are loaded lazily by JavaClassReader and if listed here,
-             they would cause an error if the package is loaded from source.
-             Sort of a HACK, indeed"
-            eachMethod mclass theNonMetaclass isJavaClass ifFalse:[
-                oldSpecEntry := oldSpec detect:[:entry | entry key = mclassName and:[ entry value = mselector]] ifNone:nil.
-                (ignoreOldEntries or:[ oldSpecEntry isNil]) ifTrue:[
-                    s spaces:8.
-                    mclassName storeArrayElementOn:s.
-                    s space.
-                    mselector storeArrayElementOn:s.
-                    s cr.
-                ]
-            ].
-        ].
-
-        s nextPutLine:'    )'
+	|oldSpec|
+
+	s nextPutLine:'extensionMethodNames'.
+	s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #extensionMethodNames) comment; nextPutLine:'"'.
+	s nextPutLine:''.
+	s nextPutLine:'    ^ #('.
+
+	oldSpec := self extensionMethodNames pairWiseCollect:[:className :selector | className -> selector ].
+
+	ignoreOldEntries ifFalse:[
+	    oldSpec do:[:entry |
+		|mclassName mselector|
+
+		mclassName := entry key asSymbol.
+		(mclassName endsWith:' class') ifTrue:[
+		    mclassName := mclassName asString.
+		].
+		mselector := entry value asSymbol.
+
+		s spaces:8.
+		mclassName storeArrayElementOn:s.
+		s space.
+		mselector storeArrayElementOn:s.
+		s cr.
+	    ].
+	].
+
+	self searchForExtensions do:[:eachMethod |
+	    |attributes oldSpecEntry mclassName mselector|
+
+	    mclassName := eachMethod mclass name.
+	    mselector := eachMethod selector.
+	    "JV@2012-09-07: Do not list Java methods in extensionMethodNames.
+	     They are loaded lazily by JavaClassReader and if listed here,
+	     they would cause an error if the package is loaded from source.
+	     Sort of a HACK, indeed"
+	    eachMethod mclass theNonMetaclass isJavaClass ifFalse:[
+		oldSpecEntry := oldSpec detect:[:entry | entry key = mclassName and:[ entry value = mselector]] ifNone:nil.
+		(ignoreOldEntries or:[ oldSpecEntry isNil]) ifTrue:[
+		    s spaces:8.
+		    mclassName storeArrayElementOn:s.
+		    s space.
+		    mselector storeArrayElementOn:s.
+		    s cr.
+		]
+	    ].
+	].
+
+	s nextPutLine:'    )'
     ].
 
     "
@@ -1800,40 +1800,40 @@
      otherwise, new items are added to the existing lists"
 
     aTwoArgBlock
-        value:(self classNamesAndAttributes_code_ignoreOldEntries:ignoreOldDefinition ignoreOldDefinition:ignoreOldDefinition)
-        value:'description - contents'.
+	value:(self classNamesAndAttributes_code_ignoreOldEntries:ignoreOldDefinition ignoreOldDefinition:ignoreOldDefinition)
+	value:'description - contents'.
 
     aTwoArgBlock
-        value: (self extensionMethodNames_code_ignoreOldEntries:ignoreOldDefinition)
-        value: 'description - contents'.
+	value: (self extensionMethodNames_code_ignoreOldEntries:ignoreOldDefinition)
+	value: 'description - contents'.
 
     aTwoArgBlock
-        value: self mandatoryPreRequisites_code
-        value: 'description'.
+	value: self mandatoryPreRequisites_code
+	value: 'description'.
 
     aTwoArgBlock
-        value: self referencedPreRequisites_code
-        value: 'description'.
+	value: self referencedPreRequisites_code
+	value: 'description'.
 
     (self class includesSelector:#excludedFromPreRequisites) ifFalse:[
-        aTwoArgBlock
-            value: self excludedFromPreRequisites_code
-            value: 'description'.
+	aTwoArgBlock
+	    value: self excludedFromPreRequisites_code
+	    value: 'description'.
     ].
 
     "/ JV:  No, subProjects **should not** be automatically generated.
     "/      Remember, they are not required to be loaded!! So, generate
     "/      subProjects only if there's no such method yet.
     (self class methodDictionary includesKey: #subProjects) ifFalse:[
-        aTwoArgBlock
-            value: self subProjects_code
-            value: 'description'.
+	aTwoArgBlock
+	    value: self subProjects_code
+	    value: 'description'.
     ].
 
     (self monticelloPackageName notNil and:[self respondsTo:#monticelloTimestamps_code]) ifTrue:[
-        aTwoArgBlock
-            value: self monticelloTimestamps_code
-            value: 'description - monticello'.
+	aTwoArgBlock
+	    value: self monticelloTimestamps_code
+	    value: 'description - monticello'.
     ].
 
     "Modified: / 25-11-2013 / 13:56:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1854,16 +1854,16 @@
     "/ ].
 
     #(
-        (productName productName_code)
-        (description description_code)
-        (companyName companyName_code)
-        (legalCopyright legalCopyright_code)
+	(productName productName_code)
+	(description description_code)
+	(companyName companyName_code)
+	(legalCopyright legalCopyright_code)
     ) pairsDo:[:selector :codeMethodSelector |
-        (self class includesSelector:selector) ifFalse:[
-            aTwoArgBlock
-                value: (self perform:codeMethodSelector)
-                value: 'description - project information'.
-        ].
+	(self class includesSelector:selector) ifFalse:[
+	    aTwoArgBlock
+		value: (self perform:codeMethodSelector)
+		value: 'description - project information'.
+	].
     ].
 !
 
@@ -1882,17 +1882,17 @@
      otherwise, new items are added to the existing lists"
 
     self
-        forEachContentsMethodsCodeToCompileDo:aTwoArgBlock
-        ignoreOldDefinition:ignoreOldDefinition.
+	forEachContentsMethodsCodeToCompileDo:aTwoArgBlock
+	ignoreOldDefinition:ignoreOldDefinition.
 
     self
-        forEachDescriptionMethodsCodeToCompileDo:aTwoArgBlock
-        ignoreOldDefinition:ignoreOldDefinition.
+	forEachDescriptionMethodsCodeToCompileDo:aTwoArgBlock
+	ignoreOldDefinition:ignoreOldDefinition.
 
     (self monticelloPackageName notNil and:[self respondsTo:#monticelloTimestamps_code]) ifTrue:[
-        aTwoArgBlock
-            value: self monticelloTimestamps_code
-            value: 'description - monticello'.
+	aTwoArgBlock
+	    value: self monticelloTimestamps_code
+	    value: 'description - monticello'.
     ].
 
     "Created: / 18-08-2006 / 16:22:37 / cg"
@@ -1902,9 +1902,9 @@
 
 legalCopyright_code
     ^ String streamContents:[:s |
-        s nextPutLine:'legalCopyright'.
-        s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #legalCopyright) comment; nextPutLine:'"'.
-        s cr; nextPutLine:'    ^ ', self legalCopyright storeString.
+	s nextPutLine:'legalCopyright'.
+	s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #legalCopyright) comment; nextPutLine:'"'.
+	s cr; nextPutLine:'    ^ ', self legalCopyright storeString.
     ].
 
     "
@@ -1926,22 +1926,22 @@
     preRequisites removeAllKeys:self excludedFromPreRequisites ifAbsent:[].
 
     ^ String streamContents:[:s |
-        s nextPutLine:'mandatoryPreRequisites'.
-        s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #mandatoryPreRequisites) comment; nextPutLine:'"'.
-        s nextPutLine:''.
-        s nextPutLine:'    ^ #('.
-        preRequisites keys asSortedCollection do:[:eachPackageID |
-            |reason|
-
-            s spaces:8.
-            eachPackageID asSymbol storeOn:s.
-            reason := preRequisites at:eachPackageID ifAbsent:[nil].
-            reason notEmptyOrNil ifTrue:[
-                s nextPutAll:'    "'; nextPutAll:reason anElement; nextPut:$".
-            ].
-            s cr.
-        ].
-        s nextPutLine:'    )'
+	s nextPutLine:'mandatoryPreRequisites'.
+	s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #mandatoryPreRequisites) comment; nextPutLine:'"'.
+	s nextPutLine:''.
+	s nextPutLine:'    ^ #('.
+	preRequisites keys asSortedCollection do:[:eachPackageID |
+	    |reason|
+
+	    s spaces:8.
+	    eachPackageID asSymbol storeOn:s.
+	    reason := preRequisites at:eachPackageID ifAbsent:[nil].
+	    reason notEmptyOrNil ifTrue:[
+		s nextPutAll:'    "'; nextPutAll:reason anElement; nextPut:$".
+	    ].
+	    s cr.
+	].
+	s nextPutLine:'    )'
     ].
 
     "
@@ -1958,10 +1958,10 @@
 
 productInstallDirBaseName_code
     ^ String streamContents:[:s |
-        s nextPutLine:'productInstallDirBaseName'.
-        s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #productInstallDirBaseName) comment; nextPutLine:'"'.
-        s cr;
-        nextPutLine:'    ^ (self package asCollectionOfSubstringsSeparatedByAny:'':/'') last'.
+	s nextPutLine:'productInstallDirBaseName'.
+	s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #productInstallDirBaseName) comment; nextPutLine:'"'.
+	s cr;
+	nextPutLine:'    ^ (self package asCollectionOfSubstringsSeparatedByAny:'':/'') last'.
     ].
 
     "
@@ -1991,9 +1991,9 @@
     "generate code that answers aString as the product name."
 
     ^ String streamContents:[:s |
-        s nextPutLine:'productName'.
-        s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #productName) comment; nextPutLine:'"'.
-        s cr; nextPutLine:'    ^ ',aString storeString.
+	s nextPutLine:'productName'.
+	s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #productName) comment; nextPutLine:'"'.
+	s cr; nextPutLine:'    ^ ',aString storeString.
     ].
 
     "
@@ -2013,27 +2013,27 @@
     preRequisitesColl := self searchForPreRequisites.
     preRequisites := preRequisitesColl second.
     preRequisites
-        removeAllKeys:self excludedFromPreRequisites ifAbsent:[];
-        removeAllKeys:self excludedFromRequiredPreRequisites ifAbsent:[];
-        removeAllKeys:preRequisitesColl first keys ifAbsent:[].  "remove the mandatory prerequisites"
+	removeAllKeys:self excludedFromPreRequisites ifAbsent:[];
+	removeAllKeys:self excludedFromRequiredPreRequisites ifAbsent:[];
+	removeAllKeys:preRequisitesColl first keys ifAbsent:[].  "remove the mandatory prerequisites"
 
     ^ String streamContents:[:s |
-        s nextPutLine:'referencedPreRequisites'.
-        s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #referencedPreRequisites) comment; nextPutLine:'"'.
-        s nextPutLine:''.
-        s nextPutLine:'    ^ #('.
-        preRequisites keys asSortedCollection do:[:eachPackageID |
-            |reason|
-
-            s spaces:8.
-            eachPackageID asSymbol storeOn:s.
-            reason := preRequisites at:eachPackageID ifAbsent:[nil].
-            reason notEmptyOrNil ifTrue:[
-                s nextPutAll:'    "'; nextPutAll:reason anElement; nextPut:$".
-            ].
-            s cr.
-        ].
-        s nextPutLine:'    )'
+	s nextPutLine:'referencedPreRequisites'.
+	s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #referencedPreRequisites) comment; nextPutLine:'"'.
+	s nextPutLine:''.
+	s nextPutLine:'    ^ #('.
+	preRequisites keys asSortedCollection do:[:eachPackageID |
+	    |reason|
+
+	    s spaces:8.
+	    eachPackageID asSymbol storeOn:s.
+	    reason := preRequisites at:eachPackageID ifAbsent:[nil].
+	    reason notEmptyOrNil ifTrue:[
+		s nextPutAll:'    "'; nextPutAll:reason anElement; nextPut:$".
+	    ].
+	    s cr.
+	].
+	s nextPutLine:'    )'
     ].
 
     "
@@ -2053,16 +2053,16 @@
      Returns nil if no such code is needed (because there are none)"
 
     ^ String streamContents:[:s |
-        s nextPutLine:'subProjects'.
-        s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #subProjects) comment; nextPutLine:'"'.
-        s nextPutLine:''.
-        s nextPutLine:'    ^ #('.
-        ProjectDefinition allSubclassesDo:[:each |
-            (each package startsWith:(self package,'/')) ifTrue:[
-                s nextPutLine:'        #''',each package,''''.
-            ]
-        ].
-        s nextPutLine:'    )'
+	s nextPutLine:'subProjects'.
+	s nextPutAll: '    "'; nextPutAll: (self class superclass lookupMethodFor: #subProjects) comment; nextPutLine:'"'.
+	s nextPutLine:''.
+	s nextPutLine:'    ^ #('.
+	ProjectDefinition allSubclassesDo:[:each |
+	    (each package startsWith:(self package,'/')) ifTrue:[
+		s nextPutLine:'        #''',each package,''''.
+	    ]
+	].
+	s nextPutLine:'    )'
     ].
 
     "Modified: / 05-03-2014 / 17:00:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -2070,11 +2070,11 @@
 
 svnRevisionNr_code: revisionNrOrNil
     ^ String streamContents:[:s |
-        s nextPutLine:'svnRevisionNr'.
-        s nextPutLine:'    "Return a SVN revision number of myself.'.
-        s nextPutLine:'     This number is updated after a commit"'.
-        s cr;
-        nextPutLine:'    ^ "$SVN-Revision:"''', ('%-16s' printf: (Array with: revisionNrOrNil printString)) , '''"$"'.
+	s nextPutLine:'svnRevisionNr'.
+	s nextPutLine:'    "Return a SVN revision number of myself.'.
+	s nextPutLine:'     This number is updated after a commit"'.
+	s cr;
+	nextPutLine:'    ^ "$SVN-Revision:"''', ('%-16s' printf: (Array with: revisionNrOrNil printString)) , '''"$"'.
     ].
 
     "
@@ -2174,7 +2174,7 @@
 
 excludedFromMandatoryPreRequisites
     "list packages which are to be explicitely excluded from the automatic constructed
-     mandatory prerequisites list. 
+     mandatory prerequisites list.
      If empty, everything that is found along the inheritance of any of
      my classes is considered to be a prerequisite package."
 
@@ -2183,9 +2183,9 @@
 
 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). 
+     prerequisites lists (both).
      If empty, everything that is found along the inheritance of any of
      my classes is considered to be a prerequisite package."
 
@@ -2196,7 +2196,7 @@
 
 excludedFromRequiredPreRequisites
     "list packages which are to be explicitely excluded from the automatic constructed
-     required prerequisites list. 
+     required prerequisites list.
      If empty, everything that is found along the inheritance of any of
      my classes is considered to be a prerequisite package."
 
@@ -2253,11 +2253,11 @@
     "use an OrderedSet here, so that mandatory prerequisites come first"
 
     ^ OrderedSet new
-        addAll:self mandatoryPreRequisites;
-        addAll:self referencedPreRequisites;
-        addAll:self includedInPreRequisites;
-        removeAllFoundIn:self excludedFromPreRequisites;
-        yourself.
+	addAll:self mandatoryPreRequisites;
+	addAll:self referencedPreRequisites;
+	addAll:self includedInPreRequisites;
+	removeAllFoundIn:self excludedFromPreRequisites;
+	yourself.
 
     "Modified: / 17-08-2006 / 19:54:21 / cg"
 !
@@ -2267,19 +2267,19 @@
 
     def := self definitionClassForPackage:packageId.
     def isNil ifTrue:[
-        "Maybe the package is not loaded? Try to load it..."
-        [
-            Smalltalk loadPackage:packageId.
-            def := self definitionClassForPackage:packageId
-        ] on:PackageLoadError do:[:ex| def := nil].
+	"Maybe the package is not loaded? Try to load it..."
+	[
+	    Smalltalk loadPackage:packageId.
+	    def := self definitionClassForPackage:packageId
+	] on:PackageLoadError do:[:ex| def := nil].
     ].
     ^ def isNil ifTrue:[
-        "Still no project definition - maybe it does not exist?"
-        Transcript showCR:'Warning: no definition class for package: ', packageId.
-        ((self searchForPreRequisites:packageId)
-            fold:[:d1 :d2| d1 addAll:d2; yourself]) keys
-    ] ifFalse:[ 
-        def effectivePreRequisites 
+	"Still no project definition - maybe it does not exist?"
+	Transcript showCR:'Warning: no definition class for package: ', packageId.
+	((self searchForPreRequisites:packageId)
+	    fold:[:d1 :d2| d1 addAll:d2; yourself]) keys
+    ] ifFalse:[
+	def effectivePreRequisites
     ]
 
     "Created: / 24-02-2011 / 22:47:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -2331,27 +2331,27 @@
      or nil if none found"
 
     |p superPackage idx|
-    
+
     p := self package.
     ProjectDefinition allSubclassesDo:[:prjDef |
-        (prjDef subProjects includes:p) ifTrue:[^ prjDef].
+	(prjDef subProjects includes:p) ifTrue:[^ prjDef].
     ].
     [
-        (idx := p lastIndexOf:$/) ~~ 0 
+	(idx := p lastIndexOf:$/) ~~ 0
     ] whileTrue:[
-        |defClass|
-        
-        superPackage := p copyTo:idx-1.
-        (defClass := ProjectDefinition definitionClassForPackage:superPackage) notNil ifTrue:[
-            ^ defClass
-        ].
-        p := superPackage.
-    ].    
+	|defClass|
+
+	superPackage := p copyTo:idx-1.
+	(defClass := ProjectDefinition definitionClassForPackage:superPackage) notNil ifTrue:[
+	    ^ defClass
+	].
+	p := superPackage.
+    ].
     ^ nil
 
     "
-     stx_goodies_refactoryBrowser_lint superProject 
-     exept_expecco_plugin_guiBrowser superProject 
+     stx_goodies_refactoryBrowser_lint superProject
+     exept_expecco_plugin_guiBrowser superProject
     "
 
     "Created: / 15-02-2017 / 16:49:05 / cg"
@@ -2387,7 +2387,7 @@
 additionalBaseAddressDefinition_bc_dot_mak
     "allows for a base-address definition to be added to the bc.mak file.
      Subclasses may redefine this to something like
-        LIB_BASE=$(LIBWIDG_BASE)
+	LIB_BASE=$(LIBWIDG_BASE)
      This will be inserted BEFORE the 'include stdHeader'
     "
 
@@ -2433,18 +2433,18 @@
      generate a rule to create the header file only."
 
     ^ String streamContents:[:s |
-        (self extensionClassesWithSuperclasses:true) do:[:eachExtendedClass |
-            |headerFileDirPath baseFilename|
-
-            (eachExtendedClass isLoaded not or:[eachExtendedClass wasAutoloaded]) ifTrue:[
-                headerFileDirPath := self pathToPackage:eachExtendedClass package withSeparator:pathSeparator.
-                baseFilename := self filenameForClass:eachExtendedClass.
-
-                s nextPutAll:(template
-                                bindWith:headerFileDirPath
-                                with:baseFilename).
-            ]
-        ].
+	(self extensionClassesWithSuperclasses:true) do:[:eachExtendedClass |
+	    |headerFileDirPath baseFilename|
+
+	    (eachExtendedClass isLoaded not or:[eachExtendedClass wasAutoloaded]) ifTrue:[
+		headerFileDirPath := self pathToPackage:eachExtendedClass package withSeparator:pathSeparator.
+		baseFilename := self filenameForClass:eachExtendedClass.
+
+		s nextPutAll:(template
+				bindWith:headerFileDirPath
+				with:baseFilename).
+	    ]
+	].
     ].
 
     "Created: / 12-09-2011 / 16:23:52 / cg"
@@ -2454,8 +2454,8 @@
     "rules for header files (of autoloaded classes)"
 
     ^ self
-        additionalHeaderRulesUsingTemplate:(self singleHeaderRuleTemplate_bc_dot_mak)
-        withSeparator:'\'
+	additionalHeaderRulesUsingTemplate:(self singleHeaderRuleTemplate_bc_dot_mak)
+	withSeparator:'\'
 
     "Created: / 12-09-2011 / 15:44:09 / cg"
 !
@@ -2464,8 +2464,8 @@
     "rules for header files (of autoloaded classes)"
 
     ^ self
-        additionalHeaderRulesUsingTemplate:(self singleHeaderRuleTemplate_make_dot_proto)
-        withSeparator:'/'
+	additionalHeaderRulesUsingTemplate:(self singleHeaderRuleTemplate_make_dot_proto)
+	withSeparator:'/'
 
     "Created: / 12-09-2011 / 15:44:28 / cg"
 !
@@ -2509,51 +2509,51 @@
     rules := '' writeStream.
     processed := Set new.
     [ cls ~~ Object ] whileTrue:[
-        cls class selectorsAndMethodsDo:[:selector :method |
-            method annotationsAt: #file:target: orAt:#file:target:extends: do: [ :annotation |
-                (processed includes: selector) ifFalse:[
-                    | file target extends contents |
-
-                    processed add: selector.
-                    file := annotation argumentAt: 1.
-                    target := annotation argumentAt: 2.
-                    annotation key == #file:target:extends: ifTrue:[ 
-                        extends := annotation argumentAt: 3.
-                    ].
-                    (#('Make.proto' 'bc.mak' ) includes: file) ifFalse:[ 
-                        self error:'Only Make.proto or bc.mak can have extension rules!!'
-                    ].
-                    extends notNil ifTrue:[
-                        file = 'Make.proto' ifTrue:[ 
-                            (#('all' 'clean' ) includes: extends) ifFalse:[ 
-                                self error: ('Rule %1 cannot be extended. Check documentation to see which rules can be extended' bindWith: extends).
-                            ].
-                        ].
-                        file = 'bc.mak' ifTrue:[ 
-                            (#('ALL' 'clean') includes: extends) ifFalse:[ 
-                                self error: ('Rule %1 cannot be extended. Check documentation to see which rules can be extended' bindWith: extends).
-                            ].
-                        ].
-                    ].
-
-                    (fileToGenerateFor = file and:[(contents := self perform: selector) notNil]) ifTrue:[ 
-                        rules nextPutAll: contents.
-                        rules cr.
-                        extends notNil ifTrue:[ 
-                            rules nextPutAll: extends; nextPutAll:'::'; space; nextPutLine: target; cr.
-                        ].
-                    ].
-                ].
-            ]
-        ].
-        cls := cls superclass.
-    ].
-    fileToGenerateFor = 'Make.proto' ifTrue:[ 
-        rules nextPutAll: self additionalRules_make_dot_proto.
-    ] ifFalse:[ 
-        fileToGenerateFor = 'bc.mak' ifTrue:[ 
-            rules nextPutAll: self additionalRules_bc_dot_mak
-        ]
+	cls class selectorsAndMethodsDo:[:selector :method |
+	    method annotationsAt: #file:target: orAt:#file:target:extends: do: [ :annotation |
+		(processed includes: selector) ifFalse:[
+		    | file target extends contents |
+
+		    processed add: selector.
+		    file := annotation argumentAt: 1.
+		    target := annotation argumentAt: 2.
+		    annotation key == #file:target:extends: ifTrue:[
+			extends := annotation argumentAt: 3.
+		    ].
+		    (#('Make.proto' 'bc.mak' ) includes: file) ifFalse:[
+			self error:'Only Make.proto or bc.mak can have extension rules!!'
+		    ].
+		    extends notNil ifTrue:[
+			file = 'Make.proto' ifTrue:[
+			    (#('all' 'clean' ) includes: extends) ifFalse:[
+				self error: ('Rule %1 cannot be extended. Check documentation to see which rules can be extended' bindWith: extends).
+			    ].
+			].
+			file = 'bc.mak' ifTrue:[
+			    (#('ALL' 'clean') includes: extends) ifFalse:[
+				self error: ('Rule %1 cannot be extended. Check documentation to see which rules can be extended' bindWith: extends).
+			    ].
+			].
+		    ].
+
+		    (fileToGenerateFor = file and:[(contents := self perform: selector) notNil]) ifTrue:[
+			rules nextPutAll: contents.
+			rules cr.
+			extends notNil ifTrue:[
+			    rules nextPutAll: extends; nextPutAll:'::'; space; nextPutLine: target; cr.
+			].
+		    ].
+		].
+	    ]
+	].
+	cls := cls superclass.
+    ].
+    fileToGenerateFor = 'Make.proto' ifTrue:[
+	rules nextPutAll: self additionalRules_make_dot_proto.
+    ] ifFalse:[
+	fileToGenerateFor = 'bc.mak' ifTrue:[
+	    rules nextPutAll: self additionalRules_bc_dot_mak
+	]
     ].
     ^ rules contents asStringCollection withTabs asString.
 
@@ -2585,7 +2585,7 @@
 ' bindWith: self name.
 
     "
-        stx_libscm_mercurial additionalRulesHG_bc_dot_mak
+	stx_libscm_mercurial additionalRulesHG_bc_dot_mak
     "
 
     "Created: / 28-11-2012 / 10:15:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -2606,7 +2606,7 @@
 ' bindWith: self name.
 
     "
-        stx_libscm_mercurial additionalRulesHG_make_dot_proto
+	stx_libscm_mercurial additionalRulesHG_make_dot_proto
     "
 
     "Created: / 28-11-2012 / 10:12:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -2620,28 +2620,28 @@
 # Update SVN revision in package definition class
 ifneq (,$(findstring .svn,$(wildcard .svn)))
 .svnversion: *.st
-        if [ -d .svn ]; then \
-                rev=$(shell svnversion -n); \
-                echo -n $$rev > .svnversion; \
-        else \
-                echo -n exported > .svnversion; \
-        fi
+	if [ -d .svn ]; then \
+		rev=$(shell svnversion -n); \
+		echo -n $$rev > .svnversion; \
+	else \
+		echo -n exported > .svnversion; \
+	fi
 
 %1.o: %1.st .svnversion
-        @if [ -d .svn ]; then \
-                rev2="$(shell printf "%-16s" $$(cat .svnversion))"; \
-                echo "  [SV]  Expanding svnRevisionNo in $1.st"; \
-                sed -e "s/\"\$$SVN\-Revision:\".*\"\$$\"/\"\$$SVN-Revision:\"\''$$rev2\''\"\$$\"/g" $< > .%1.svn.st; \
-        fi
-        $(MAKE) CC="$(CLASSLIB_CC)" OPT="$(OPT)" SEPINITCODE="$(SEPINITCODE)" STC="$(STC)" STFILE=.%1.svn $(C_RULE);
-        sed -i -e "s/\".%1.svn.st\");/\"\%1.st\");/g" .%1.svn.c
-        $(MAKE) .%1.svn.$(O)
-        @mv .%1.svn.$(O) %1.$(O)
+	@if [ -d .svn ]; then \
+		rev2="$(shell printf "%-16s" $$(cat .svnversion))"; \
+		echo "  [SV]  Expanding svnRevisionNo in $1.st"; \
+		sed -e "s/\"\$$SVN\-Revision:\".*\"\$$\"/\"\$$SVN-Revision:\"\''$$rev2\''\"\$$\"/g" $< > .%1.svn.st; \
+	fi
+	$(MAKE) CC="$(CLASSLIB_CC)" OPT="$(OPT)" SEPINITCODE="$(SEPINITCODE)" STC="$(STC)" STFILE=.%1.svn $(C_RULE);
+	sed -i -e "s/\".%1.svn.st\");/\"\%1.st\");/g" .%1.svn.c
+	$(MAKE) .%1.svn.$(O)
+	@mv .%1.svn.$(O) %1.$(O)
 endif
 ' bindWith: self name.
 
     "
-        stx_libbasic3 additionalRulesSvn_make_dot_proto
+	stx_libbasic3 additionalRulesSvn_make_dot_proto
     "
 
     "Created: / 24-06-2009 / 21:33:32 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -2829,12 +2829,12 @@
     "see the stc reference / stc usage for options.
      Can be redefined in concrete packages.
      For now, the following variants are useful:
-        +optspace3                  most compact code
-                                    - use for all gui, application code.
-
-        +optinline +optinline2 +inlineNew
-                                    fastest code
-                                    - use only for computation-intensive classes"
+	+optspace3                  most compact code
+				    - use for all gui, application code.
+
+	+optinline +optinline2 +inlineNew
+				    fastest code
+				    - use only for computation-intensive classes"
 
     ^ '+optspace3'
 
@@ -2845,9 +2845,9 @@
     "see the stc reference / stc usage for options.
      Can be redefined in concrete packages.
      For now, the following variants are useful:
-        -warn                   no warnings
-        -warnNonStandard        no warnings about non-standard smalltalk features
-        -warnUnused             no warnings about unused variables"
+	-warn                   no warnings
+	-warnNonStandard        no warnings about non-standard smalltalk features
+	-warnUnused             no warnings about unused variables"
 
     ^ '-warnNonStandard'
 
@@ -2965,13 +2965,13 @@
      Other systems may put it elsewhere, or ignore it."
 
     |m|
-    
+
     m := self module.
     (m = 'stx') ifTrue:[
-        ^ 'Claus Gittinger & eXept Software AG'  
+	^ 'Claus Gittinger & eXept Software AG'
     ].
     (m = 'exept') ifTrue:[
-        ^ 'eXept Software AG'  
+	^ 'eXept Software AG'
     ].
     ^ 'My Company'
 
@@ -3080,10 +3080,10 @@
     "<major>.<minor>.<rev>.<rel> (such as '1.2.17.1') "
 
     ^ '%1.%2.%3.%4'
-        bindWith:self fileMajorVersionNr
-        with:self fileMinorVersionNr
-        with:self fileRevisionNr
-        with:self fileReleaseNr.
+	bindWith:self fileMajorVersionNr
+	with:self fileMinorVersionNr
+	with:self fileRevisionNr
+	with:self fileReleaseNr.
 
     "
      self fileVersion
@@ -3098,10 +3098,10 @@
     "<major>,<minor>,<revision>,<release> (such as '2,17,1,2') "
 
     ^ '%1,%2,%3,%4'
-        bindWith:self fileMajorVersionNr
-        with:self fileMinorVersionNr
-        with:self fileRevisionNr
-        with:self fileReleaseNr.
+	bindWith:self fileMajorVersionNr
+	with:self fileMinorVersionNr
+	with:self fileRevisionNr
+	with:self fileReleaseNr.
 
     "Created: / 17-08-2006 / 20:16:17 / cg"
     "Modified: / 30-08-2006 / 18:54:20 / cg"
@@ -3121,20 +3121,20 @@
      Other systems may put it elsewhere, or ignore it."
 
     |m thisYear template|
-     
+
     m := self module.
     thisYear := Date today year.
 
     m = 'stx' ifTrue:[
-        "hardwired-default"
-        template := 'Copyright Claus Gittinger %1\nCopyright eXept Software AG %1' 
+	"hardwired-default"
+	template := 'Copyright Claus Gittinger %1\nCopyright eXept Software AG %1'
     ] ifFalse:[
-        m = 'exept' ifTrue:[
-            "hardwired-default"
-            template := 'Copyright eXept Software AG %1' 
-        ] ifFalse:[
-            template := 'My CopyRight or CopyLeft %1'
-        ].
+	m = 'exept' ifTrue:[
+	    "hardwired-default"
+	    template := 'Copyright eXept Software AG %1'
+	] ifFalse:[
+	    template := 'My CopyRight or CopyLeft %1'
+	].
     ].
     ^ template bindWith:thisYear
 
@@ -3252,10 +3252,10 @@
 
     m := self module.
     m = 'stx' ifTrue:[
-        ^ 'Smalltalk/X'
+	^ 'Smalltalk/X'
     ].
     m = 'exept' ifTrue:[
-        ^ 'eXept AddOns'
+	^ 'eXept AddOns'
     ].
     ^ nil.
 
@@ -3285,7 +3285,7 @@
     "Returns a product publisher which will appear in <app>.nsi."
 
     ( #('exept' 'stx') includes:self module) ifTrue:[
-        ^ 'eXept Software AG'
+	^ 'eXept Software AG'
     ].
 
     ^ self companyName
@@ -3307,10 +3307,10 @@
     "<major>.<minor>.<revision>.<release> (such as '5.3.2.1')"
 
     ^ '%1.%2.%3.%4'
-        bindWith:self majorVersionNr
-        with:self minorVersionNr
-        with:self revisionNr
-        with:self releaseNr.
+	bindWith:self majorVersionNr
+	with:self minorVersionNr
+	with:self revisionNr
+	with:self releaseNr.
 
     "
      self productVersion
@@ -3325,10 +3325,10 @@
     "<major>.<minor>.<revision>.<release> (such as '0,1,1,1') "
 
     ^ '%1,%2,%3,%4'
-        bindWith:self majorVersionNr
-        with:self minorVersionNr
-        with:self revisionNr
-        with:self releaseNr.
+	bindWith:self majorVersionNr
+	with:self minorVersionNr
+	with:self revisionNr
+	with:self releaseNr.
 
     "
      self productVersionCommaSeparated
@@ -3342,7 +3342,7 @@
     "Returns a product webSite which will appear in <app>.nsi."
 
     ( #('exept' 'stx') includes:self module) ifTrue:[
-        ^ 'http://www.exept.de'
+	^ 'http://www.exept.de'
     ].
 
     "/ should be redefined by concrete ApplicationDefinition
@@ -3380,12 +3380,12 @@
 
 supportedLanguages
     "Returns a list of languages that (should be / are) supported by this application or library.
-     Currently this is only used by lint, to verify that the corresponding languages are 
+     Currently this is only used by lint, to verify that the corresponding languages are
      present in the resource files."
 
     self module = 'stx' ifTrue:[
-        ^ #(en de)
-    ].    
+	^ #(en de)
+    ].
     ^ #(en)
 
     "
@@ -3411,7 +3411,7 @@
      Return #( '*' ) to get doc files for all classes"
 
     ^ #(
-        '*'
+	'*'
     )
 !
 
@@ -3421,9 +3421,9 @@
      to be deployed."
 
     self classes do:[:eachClass |
-        (self autoDocClassNamePatterns contains:[:pattern | pattern match:eachClass name]) ifTrue:[
-            self generateClassDocumentationFor:eachClass.
-        ]
+	(self autoDocClassNamePatterns contains:[:pattern | pattern match:eachClass name]) ifTrue:[
+	    self generateClassDocumentationFor:eachClass.
+	]
     ].
 ! !
 
@@ -3443,37 +3443,37 @@
     | dict cls |
 
     dict := OrderedDictionary withKeysAndValues:#(
-          'Make.spec'         #'generate_make_dot_spec'
-          'Make.proto'        #'generate_make_dot_proto'
-          "/ cg: changed to generate Makefile.init instead of Makefile,
-          "/     because macosx files are not case sensitive.
-          "/ You will have to execute make -f Makefile.init initially
-          "/ 'Makefile'          #'generate_makefile'          "/ for unix
-          'Makefile.init'     #'generate_makefile'          "/ for unix
-          'bc.mak'            #'generate_bc_dot_mak'        "/ for windows
-          'abbrev.stc'        #'generate_abbrev_dot_stc'
-          'bmake.bat'         #'generate_bmake_dot_mak'     "/ for bcc32
-          'vcmake.bat'        #'generate_vcmake_dot_mak'    "/ for msvc
-          "/ 'lccmake.bat'       #'generate_lccmake_dot_mak'   "/ for lcc - not supported at the moment
-          "/ 'tccmake.bat'       #'generate_tccmake_dot_mak'     "/ for tcc - cannot link at the moment
-          'mingwmake.bat'     #'generate_mingwmake_dot_mak'   "/ for mingw
+	  'Make.spec'         #'generate_make_dot_spec'
+	  'Make.proto'        #'generate_make_dot_proto'
+	  "/ cg: changed to generate Makefile.init instead of Makefile,
+	  "/     because macosx files are not case sensitive.
+	  "/ You will have to execute make -f Makefile.init initially
+	  "/ 'Makefile'          #'generate_makefile'          "/ for unix
+	  'Makefile.init'     #'generate_makefile'          "/ for unix
+	  'bc.mak'            #'generate_bc_dot_mak'        "/ for windows
+	  'abbrev.stc'        #'generate_abbrev_dot_stc'
+	  'bmake.bat'         #'generate_bmake_dot_mak'     "/ for bcc32
+	  'vcmake.bat'        #'generate_vcmake_dot_mak'    "/ for msvc
+	  "/ 'lccmake.bat'       #'generate_lccmake_dot_mak'   "/ for lcc - not supported at the moment
+	  "/ 'tccmake.bat'       #'generate_tccmake_dot_mak'     "/ for tcc - cannot link at the moment
+	  'mingwmake.bat'     #'generate_mingwmake_dot_mak'   "/ for mingw
     ).
 
     dict
-        at:self rcFilename      put:#'generate_packageName_dot_rc'.             "/ for windows
+	at:self rcFilename      put:#'generate_packageName_dot_rc'.             "/ for windows
 
     "Add additional custom files as specified in file:overwrite: annotations"
     cls := self.
     [ cls ~~ Object ] whileTrue:[
-        cls class selectorsAndMethodsDo:[:selector :method |
-            | annotation |
-
-            annotation := method annotationAt: #file:overwrite:.
-            annotation notNil ifTrue:[ 
-                dict at: (annotation argumentAt: 1) put: selector
-            ].
-        ].
-        cls := cls superclass.
+	cls class selectorsAndMethodsDo:[:selector :method |
+	    | annotation |
+
+	    annotation := method annotationAt: #file:overwrite:.
+	    annotation notNil ifTrue:[
+		dict at: (annotation argumentAt: 1) put: selector
+	    ].
+	].
+	cls := cls superclass.
     ].
 
     ^ dict.
@@ -3507,12 +3507,12 @@
 
     pairs := OrderedCollection new.
     self fileNamesToGenerate keysDo:[:fileName |
-        |fileContents|
-
-        fileContents := self generateFile:fileName.
-        fileContents notNil ifTrue:[
-            pairs add:(Array with:fileName with:fileContents)
-        ].
+	|fileContents|
+
+	fileContents := self generateFile:fileName.
+	fileContents notNil ifTrue:[
+	    pairs add:(Array with:fileName with:fileContents)
+	].
     ].
 
     pairs pairsDo:aTwoArgBlock
@@ -3526,32 +3526,32 @@
     |action missingNames|
 
     (#('bc.mak' 'Make.proto' 'loadAll') includes:filename) ifTrue:[
-        "if there are missing classes in image, the dependencies cannot be computed.
-         Warn the user"
-
-        missingNames := self allClassNames "compiled_classNames"
-                                    select:[:aName |
-                                        |cls|
-
-                                        cls := environment at:aName asSymbol.
-                                        cls isNil
-                                    ].
-        missingNames notEmpty ifTrue:[
-            (self confirm:(self classResources stringWithCRs:'While generating %1:\Some classes from the list of compiled classes are missing in the image:\\%2\\If you continue, you have to fix dependencies for these classes in %1 manually!!\\Continue anyway?'
-                                        with:filename with:(missingNames asStringWith:', ')))
-            ifFalse:[^ nil].
-        ].
+	"if there are missing classes in image, the dependencies cannot be computed.
+	 Warn the user"
+
+	missingNames := self allClassNames "compiled_classNames"
+				    select:[:aName |
+					|cls|
+
+					cls := Smalltalk at:aName asSymbol.
+					cls isNil
+				    ].
+	missingNames notEmpty ifTrue:[
+	    (self confirm:(self classResources stringWithCRs:'While generating %1:\Some classes from the list of compiled classes are missing in the image:\\%2\\If you continue, you have to fix dependencies for these classes in %1 manually!!\\Continue anyway?'
+					with:filename with:(missingNames asStringWith:', ')))
+	    ifFalse:[^ nil].
+	].
     ].
 
     action := self basicFileNamesToGenerate at:filename ifAbsent:[].
     action notNil ifTrue:[
-        ^ self perform:action
+	^ self perform:action
     ].
     (filename = 'app.rc' or:[filename = 'lib.rc' or:[filename = self rcFilename]]) ifTrue:[
-        ^ self generate_packageName_dot_rc
+	^ self generate_packageName_dot_rc
     ].
     (filename = 'loadAll') ifTrue:[
-        ^ self generate_loadAll
+	^ self generate_loadAll
     ].
     self error:('File "%1" not appropriate (not generated) for this type of project.' bindWith:filename)
 
@@ -3567,7 +3567,7 @@
     (dir / (filename asFilename baseName)) contents:(self generateFile: filename).
 
     "
-        stx_projects_smalltalk generateFile:'package.deps.rake' in: '/tmp'
+	stx_projects_smalltalk generateFile:'package.deps.rake' in: '/tmp'
     "
 
     "Created: / 26-02-2011 / 10:42:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -3582,18 +3582,18 @@
 
     firstLine := true.
     self searchForClasses do:[:eachClass|
-        eachClass isJavaClass ifFalse:[
-            firstLine ifTrue:[
-                aStream nextPutAll:'cvs rm -f '.
-                firstLine := false.
-            ].
-            eachClass classFilename ~= (eachClass generateClassFilename, '.st') ifTrue:[
-                aStream nextPutAll:eachClass classBaseFilename; space.
-            ]
-        ].
+	eachClass isJavaClass ifFalse:[
+	    firstLine ifTrue:[
+		aStream nextPutAll:'cvs rm -f '.
+		firstLine := false.
+	    ].
+	    eachClass classFilename ~= (eachClass generateClassFilename, '.st') ifTrue:[
+		aStream nextPutAll:eachClass classBaseFilename; space.
+	    ]
+	].
     ].
     firstLine ifFalse:[
-        aStream cr.
+	aStream cr.
     ].
 
     "
@@ -3607,13 +3607,13 @@
     "generate a shell script to rename broken class filenames"
 
     self searchForClasses do:[:eachClass|
-        eachClass isJavaClass ifFalse:[
-            eachClass classFilename ~= (eachClass generateClassFilename, '.st') ifTrue:[
-                aStream nextPutAll:'cp ';
-                       nextPutAll:eachClass classBaseFilename; nextPutAll:',v ';
-                       nextPutAll:eachClass generateClassFilename; nextPutAll:'.st,v'; cr.
-            ]
-        ]
+	eachClass isJavaClass ifFalse:[
+	    eachClass classFilename ~= (eachClass generateClassFilename, '.st') ifTrue:[
+		aStream nextPutAll:'cp ';
+		       nextPutAll:eachClass classBaseFilename; nextPutAll:',v ';
+		       nextPutAll:eachClass generateClassFilename; nextPutAll:'.st,v'; cr.
+	    ]
+	]
     ].
 
     "
@@ -3628,80 +3628,80 @@
    self checkIfClassesArePresent.
 
     ^ String
-        streamContents:[:s |
-            |addEntry|
-
-            addEntry :=
-                [:eachClassName |
-                    |cls fn wasLoaded failedToLoad numClassInstvars|
-
-                    s nextPutAll:eachClassName.
-                    s nextPutAll:' '.
-
-                    cls := Smalltalk classNamed:eachClassName.
-                    cls isNil ifTrue:[
-                        fn := self filenameForClass:eachClassName.
-                        s nextPutAll:fn.
-                        s nextPutAll:' '; nextPutAll:(self package); nextPutAll:' '.
-                        s nextPutAll:' '; nextPutAll:'unknownCategory' storeString; nextPutAll:' '.
-                        s nextPutAll:' '; nextPutAll:'0'.
-                    ] ifFalse:[
-                        wasLoaded := cls isLoaded.
-                        wasLoaded ifFalse:[
-                            failedToLoad := false.
-
-                            Error handle:[:ex |
-                                failedToLoad := true.
-                            ] do:[
-                                ParserFlags
-                                    withSTCCompilation:#never
-                                    do:[
-                                        cls autoload.
-                                    ]
-                            ].
-                        ].
-
-                        fn := self filenameForClass:cls.
-                        (fn includes:Character space) ifTrue:[
-                            s nextPutAll:fn storeString.
-                        ] ifFalse:[
-                            s nextPutAll:fn.
-                        ].
-                        s nextPutAll:' '; nextPutAll:(self package); nextPutAll:' '.
-                        s nextPutAll: (cls category asString storeString).
-                        failedToLoad ifTrue:[
-                            s nextPutAll:' 0'.
-                        ] ifFalse:[
-                            numClassInstvars := cls theMetaclass instSize - Class instSize.
-                            s nextPutAll:' '; nextPutAll:numClassInstvars printString.
-                        ].
-
-                        wasLoaded ifFalse:[
-                            UserPreferences current autoUnloadAutoloadedClassesInProjectDefinition ifTrue:[
-                                cls unload
-                            ]
-                        ]
-                    ].
-                    s cr.
-                ].
-
-            s nextPutLine:'# automagically generated by the project definition'.
-            s nextPutLine:'# this file is needed for stc to be able to compile modules independently.'.
-            s nextPutLine:'# it provides information about a classes filename, category and especially namespace.'.
-
-            self allClassNames do:addEntry.
-            self namesAndAttributesIn:(self additionalClassNamesAndAttributes) do: [:nm :attr |
-                (attr isEmptyOrNil or:[(attr includes:#autoload) not]) ifTrue:[
-                    addEntry value:nm
-                ].
-            ].
-        ]
-
-    "
-        stx_libbasic generate_abbrev_dot_stc
-        DapasXProject generate_abbrev_dot_stc
-        DapasX_Datenbasis generate_abbrev_dot_stc
-        bosch_dapasx_interactiver_editor generate_abbrev_dot_stc
+	streamContents:[:s |
+	    |addEntry|
+
+	    addEntry :=
+		[:eachClassName |
+		    |cls fn wasLoaded failedToLoad numClassInstvars|
+
+		    s nextPutAll:eachClassName.
+		    s nextPutAll:' '.
+
+		    cls := Smalltalk classNamed:eachClassName.
+		    cls isNil ifTrue:[
+			fn := self filenameForClass:eachClassName.
+			s nextPutAll:fn.
+			s nextPutAll:' '; nextPutAll:(self package); nextPutAll:' '.
+			s nextPutAll:' '; nextPutAll:'unknownCategory' storeString; nextPutAll:' '.
+			s nextPutAll:' '; nextPutAll:'0'.
+		    ] ifFalse:[
+			wasLoaded := cls isLoaded.
+			wasLoaded ifFalse:[
+			    failedToLoad := false.
+
+			    Error handle:[:ex |
+				failedToLoad := true.
+			    ] do:[
+				ParserFlags
+				    withSTCCompilation:#never
+				    do:[
+					cls autoload.
+				    ]
+			    ].
+			].
+
+			fn := self filenameForClass:cls.
+			(fn includes:Character space) ifTrue:[
+			    s nextPutAll:fn storeString.
+			] ifFalse:[
+			    s nextPutAll:fn.
+			].
+			s nextPutAll:' '; nextPutAll:(self package); nextPutAll:' '.
+			s nextPutAll: (cls category asString storeString).
+			failedToLoad ifTrue:[
+			    s nextPutAll:' 0'.
+			] ifFalse:[
+			    numClassInstvars := cls theMetaclass instSize - Class instSize.
+			    s nextPutAll:' '; nextPutAll:numClassInstvars printString.
+			].
+
+			wasLoaded ifFalse:[
+			    UserPreferences current autoUnloadAutoloadedClassesInProjectDefinition ifTrue:[
+				cls unload
+			    ]
+			]
+		    ].
+		    s cr.
+		].
+
+	    s nextPutLine:'# automagically generated by the project definition'.
+	    s nextPutLine:'# this file is needed for stc to be able to compile modules independently.'.
+	    s nextPutLine:'# it provides information about a classes filename, category and especially namespace.'.
+
+	    self allClassNames do:addEntry.
+	    self namesAndAttributesIn:(self additionalClassNamesAndAttributes) do: [:nm :attr |
+		(attr isEmptyOrNil or:[(attr includes:#autoload) not]) ifTrue:[
+		    addEntry value:nm
+		].
+	    ].
+	]
+
+    "
+	stx_libbasic generate_abbrev_dot_stc
+	DapasXProject generate_abbrev_dot_stc
+	DapasX_Datenbasis generate_abbrev_dot_stc
+	bosch_dapasx_interactiver_editor generate_abbrev_dot_stc
     "
 
     "Created: / 09-08-2006 / 11:24:39 / fm"
@@ -3711,8 +3711,8 @@
 generate_autopackage_default_dot_apspec
 
     ^self
-        replaceMappings: self autopackage_default_dot_apspec_mappings
-        in: self autopackage_default_dot_apspec
+	replaceMappings: self autopackage_default_dot_apspec_mappings
+	in: self autopackage_default_dot_apspec
 
     "
      stx_projects_smalltalk generate_autopackage_default_dot_apspec
@@ -3723,8 +3723,8 @@
 
 generate_bc_dot_mak
     ^ (self
-        replaceMappings: self bc_dot_mak_mappings
-        in: self bc_dot_mak) asStringCollection withTabs asString
+	replaceMappings: self bc_dot_mak_mappings
+	in: self bc_dot_mak) asStringCollection withTabs asString
 
     "
      DapasXProject generate_bc_dot_mak
@@ -3737,14 +3737,14 @@
 generate_bmake_dot_mak
 
     ^self replaceMappings: self bmake_dot_mak_mappings
-            in: self bmake_dot_mak
+	    in: self bmake_dot_mak
 
     "Created: / 17-08-2006 / 20:03:43 / cg"
 !
 
 generate_builder_baseline_dot_rbspec
     ^ self replaceMappings:self builder_baseline_dot_rbspec_mappings
-        in:self builder_baseline_dot_rbspec
+	in:self builder_baseline_dot_rbspec
 
     "
      stx_projects_smalltalk generate_builder_baseline_dot_rbspec
@@ -3757,30 +3757,30 @@
 generate_lccmake_dot_mak
 
     ^self replaceMappings: self bmake_dot_mak_mappings
-            in: self lccmake_dot_mak
+	    in: self lccmake_dot_mak
 
     "Created: / 03-09-2012 / 19:49:56 / cg"
 !
 
 generate_loadAll
     ^ String
-        streamContents:[:s |
-            |classNames classesLoaded classNamesUnloaded classesSorted|
-
-            classNames := self compiled_classNames_common.
-            classesLoaded := classNames
-                        collect:[:nm | Smalltalk classNamed:nm]
-                        thenSelect:[:cls |  cls notNil and:[cls isLoaded] ].
-            classNamesUnloaded := classNames
-                        select:[:nm |
-                            |cls|
-                            cls := Smalltalk classNamed:nm.
-                            cls isNil or:[cls isLoaded not]
-                        ].
-
-            classesSorted := Class classesSortedByLoadOrder:classesLoaded.
-
-            s nextPutAll:'"/
+	streamContents:[:s |
+	    |classNames classesLoaded classNamesUnloaded classesSorted|
+
+	    classNames := self compiled_classNames_common.
+	    classesLoaded := classNames
+			collect:[:nm | Smalltalk classNamed:nm]
+			thenSelect:[:cls |  cls notNil and:[cls isLoaded] ].
+	    classNamesUnloaded := classNames
+			select:[:nm |
+			    |cls|
+			    cls := Smalltalk classNamed:nm.
+			    cls isNil or:[cls isLoaded not]
+			].
+
+	    classesSorted := Class classesSortedByLoadOrder:classesLoaded.
+
+	    s nextPutAll:'"/
 "/ $' , 'Header' , '$
 "/
 "/ loadAll-file to fileIn code for: ' , self package , '
@@ -3805,24 +3805,24 @@
 files := #(
 '.
 
-            classesSorted do:[:eachClass |
-                s nextPutLine:'  ''' , (self filenameForClass:eachClass), ''''.
-            ].
-            classNamesUnloaded do:[:nm |
-                s nextPutLine:'  ''' , (self filenameForClass:nm), ''''.
-            ].
-
-            self namesAndAttributesIn:(self additionalClassNamesAndAttributes) do:[:nm :attr |
-                (attr isEmptyOrNil or:[(attr includes:#autoload) not]) ifTrue:[
-                    s nextPutLine:'  ''' , (self filenameForClass:nm), ''''.
-                ].
-            ].
-
-            self hasExtensionMethods ifTrue:[
-                s nextPutLine:'  ''extensions.st'''.
-            ].
-
-            s nextPutAll:'
+	    classesSorted do:[:eachClass |
+		s nextPutLine:'  ''' , (self filenameForClass:eachClass), ''''.
+	    ].
+	    classNamesUnloaded do:[:nm |
+		s nextPutLine:'  ''' , (self filenameForClass:nm), ''''.
+	    ].
+
+	    self namesAndAttributesIn:(self additionalClassNamesAndAttributes) do:[:nm :attr |
+		(attr isEmptyOrNil or:[(attr includes:#autoload) not]) ifTrue:[
+		    s nextPutLine:'  ''' , (self filenameForClass:nm), ''''.
+		].
+	    ].
+
+	    self hasExtensionMethods ifTrue:[
+		s nextPutLine:'  ''extensions.st'''.
+	    ].
+
+	    s nextPutAll:'
 ).
 
 "/ see if there is a classLibrary
@@ -3830,11 +3830,11 @@
     |handle loaded|
 
     handle := ObjectFileLoader loadedObjectHandles
-                    detect:[:h | h package = ''' , self package , '''] ifNone:nil.
+		    detect:[:h | h package = ''' , self package , '''] ifNone:nil.
     handle ifNotNil:[
-        loaded := Set new:(handle classes size).
-        handle classes do:[:c| c isMeta ifFalse:[loaded add:c classBaseFilename]].
-        files := files \ loaded.
+	loaded := Set new:(handle classes size).
+	handle classes do:[:c| c isMeta ifFalse:[loaded add:c classBaseFilename]].
+	files := files \ loaded.
     ].
 ].
 
@@ -3844,16 +3844,16 @@
   files do:[:f |
     ''.'' infoPrint.
     f asFilename exists ifTrue:[
-        Smalltalk fileIn:f.
+	Smalltalk fileIn:f.
     ] ifFalse:[
-        Smalltalk fileIn:(''source/'' , f)
+	Smalltalk fileIn:(''source/'' , f)
     ]
   ].
   '' '' infoPrintCR.
 ].
 ''done (' , self package ,').'' infoPrintCR.
 '.
-        ].
+	].
 
     "Created: / 14-09-2006 / 14:21:31 / cg"
     "Modified: / 12-10-2006 / 15:55:00 / cg"
@@ -3862,8 +3862,8 @@
 generate_make_dot_proto
 
     ^ (self
-        replaceMappings: self make_dot_proto_mappings
-        in: self make_dot_proto) asStringCollection withTabs asString
+	replaceMappings: self make_dot_proto_mappings
+	in: self make_dot_proto) asStringCollection withTabs asString
 
     "
      stx_libbasic2 generate_make_dot_proto
@@ -3874,8 +3874,8 @@
 
 generate_make_dot_spec
     ^ (self
-        replaceMappings: self make_dot_spec_mappings
-        in: self make_dot_spec) asStringCollection withTabs asString
+	replaceMappings: self make_dot_spec_mappings
+	in: self make_dot_spec) asStringCollection withTabs asString
 
     "
      DapasXProject generate_make_dot_spec
@@ -3889,8 +3889,8 @@
 generate_makefile
 
     ^ (self
-        replaceMappings: self makefile_mappings
-        in: self makefile) asStringCollection withTabs asString
+	replaceMappings: self makefile_mappings
+	in: self makefile) asStringCollection withTabs asString
 
     "
      stx_libbasic2 generate_makefile
@@ -3900,7 +3900,7 @@
 generate_mingwmake_dot_mak
 
     ^self replaceMappings: self bmake_dot_mak_mappings
-            in: self mingwmake_dot_mak
+	    in: self mingwmake_dot_mak
 
     "Created: / 05-09-2012 / 19:44:07 / cg"
 !
@@ -3908,7 +3908,7 @@
 generate_packageName_dot_rc
 
     ^self replaceMappings: self packageName_dot_rc_mappings
-            in: self packageName_dot_rc
+	    in: self packageName_dot_rc
 
 "
   bosch_dapasx_datenbasis generate_packageName_dot_rc
@@ -3925,8 +3925,8 @@
 
 generate_package_dot_deps_dot_rake
     ^ (self replaceMappings:self package_dot_deps_dot_rake_mappings
-        in:self package_dot_deps_dot_rake) asStringCollection
-        withTabs asString
+	in:self package_dot_deps_dot_rake) asStringCollection
+	withTabs asString
 
     "
      stx_libjava generate_dependencies_dot_rake"
@@ -3937,7 +3937,7 @@
 generate_tccmake_dot_mak
 
     ^self replaceMappings: self bmake_dot_mak_mappings
-            in: self tccmake_dot_mak
+	    in: self tccmake_dot_mak
 
     "Created: / 03-09-2012 / 19:50:25 / cg"
 !
@@ -3945,12 +3945,12 @@
 generate_vcmake_dot_mak
 
     ^self replaceMappings: self bmake_dot_mak_mappings
-            in: self vcmake_dot_mak
+	    in: self vcmake_dot_mak
 !
 
 nsiFilename
     "only applications define it"
-    
+
     ^ nil.
 
     "Created: / 18-06-2018 / 14:07:43 / Claus Gittinger"
@@ -3985,26 +3985,26 @@
 
     mappings := Dictionary new.
     ^ mappings
-        at: 'TOP' put: (self pathToTopWithSeparator:'/');                 "/ unix here
+	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);
-        at: 'PRODUCT_WEBSITE' put: (self productWebSite);
-        at: 'PRODUCT_INSTALLDIR' put: (self productInstallDir);
-        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.
+	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);
+	at: 'PRODUCT_WEBSITE' put: (self productWebSite);
+	at: 'PRODUCT_INSTALLDIR' put: (self productInstallDir);
+	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.
 
 
     "Created: / 21-12-2010 / 09:00:49 / cg"
@@ -4016,22 +4016,22 @@
 
     d := self common_mappings.
     ^ d
-        at: 'TOP' put: ( self pathToTopWithSeparator:'\' );                "/ win32 here
-        at: 'MODULE_PATH' put: ( self moduleDirectory_win32 );  "/ win32 here
-        at: 'PRIMARY_TARGET' put: (self primaryTarget_bc_dot_mak);
-        at: 'ADDITIONAL_BASE_ADDRESS_DEFINITION' put: (self additionalBaseAddressDefinition_bc_dot_mak ? '');
-        at: 'ADDITIONAL_DEFINITIONS' put: (self additionalDefinitions_bc_dot_mak ? '');
-        at: 'ADDITIONAL_HEADERRULES' put: (self additionalHeaderRules_bc_dot_mak);
-        at: 'ADDITIONAL_RULES' put: (self additionalRulesFor: 'bc.mak');
-        at: 'ADDITIONAL_RULES_HG' put: (self additionalRulesHG_bc_dot_mak ? '');
-        at: 'ADDITIONAL_TARGETS' put: (self additionalTargets_bc_dot_mak ? '');
-        at: 'ADDITIONAL_LINK_LIBRARIES' put: (self additionalLinkLibraries_bc_dot_mak ? '');
-        at: 'ADDITIONAL_POSTNSISRULES' put: (self additional_post_nsis_rules);  "/ win32 bc here    
-        at: 'ADDITIONAL_POSTNSISRULES64' put: (self additional_post_nsis_rules64);  "/ win64 mingw here    
-        at: 'LOCAL_INCLUDES' put: (self generateLocalIncludes_win32 ? '');
-        at: 'LOCAL_DEFINES' put: self localDefines_win32 ? '';
-        at: 'GLOBAL_DEFINES' put: self globalDefines_win32 ? '';
-        yourself.
+	at: 'TOP' put: ( self pathToTopWithSeparator:'\' );                "/ win32 here
+	at: 'MODULE_PATH' put: ( self moduleDirectory_win32 );  "/ win32 here
+	at: 'PRIMARY_TARGET' put: (self primaryTarget_bc_dot_mak);
+	at: 'ADDITIONAL_BASE_ADDRESS_DEFINITION' put: (self additionalBaseAddressDefinition_bc_dot_mak ? '');
+	at: 'ADDITIONAL_DEFINITIONS' put: (self additionalDefinitions_bc_dot_mak ? '');
+	at: 'ADDITIONAL_HEADERRULES' put: (self additionalHeaderRules_bc_dot_mak);
+	at: 'ADDITIONAL_RULES' put: (self additionalRulesFor: 'bc.mak');
+	at: 'ADDITIONAL_RULES_HG' put: (self additionalRulesHG_bc_dot_mak ? '');
+	at: 'ADDITIONAL_TARGETS' put: (self additionalTargets_bc_dot_mak ? '');
+	at: 'ADDITIONAL_LINK_LIBRARIES' put: (self additionalLinkLibraries_bc_dot_mak ? '');
+	at: 'ADDITIONAL_POSTNSISRULES' put: (self additional_post_nsis_rules);  "/ win32 bc here
+	at: 'ADDITIONAL_POSTNSISRULES64' put: (self additional_post_nsis_rules64);  "/ win64 mingw here
+	at: 'LOCAL_INCLUDES' put: (self generateLocalIncludes_win32 ? '');
+	at: 'LOCAL_DEFINES' put: self localDefines_win32 ? '';
+	at: 'GLOBAL_DEFINES' put: self globalDefines_win32 ? '';
+	yourself.
 
     "Created: / 18-08-2006 / 11:43:39 / cg"
     "Modified: / 05-09-2012 / 10:02:51 / cg"
@@ -4041,13 +4041,13 @@
 
 bmake_dot_mak_mappings
     ^ self common_mappings
-        at:'TOP' put: ( self pathToTopWithSeparator:'\' );
-        at:'SUBPROJECT_BMAKE_CALLS' put:(self subProjectBmakeCalls);
-        at:'SUBPROJECT_VCMAKE_CALLS' put:(self subProjectVCmakeCalls);
-        at:'SUBPROJECT_LCCMAKE_CALLS' put:(self subProjectLCCmakeCalls);
-        at:'SUBPROJECT_TCCMAKE_CALLS' put:(self subProjectTCCmakeCalls);
-        at:'SUBPROJECT_MINGWMAKE_CALLS' put:(self subProjectMingwmakeCalls);
-        yourself
+	at:'TOP' put: ( self pathToTopWithSeparator:'\' );
+	at:'SUBPROJECT_BMAKE_CALLS' put:(self subProjectBmakeCalls);
+	at:'SUBPROJECT_VCMAKE_CALLS' put:(self subProjectVCmakeCalls);
+	at:'SUBPROJECT_LCCMAKE_CALLS' put:(self subProjectLCCmakeCalls);
+	at:'SUBPROJECT_TCCMAKE_CALLS' put:(self subProjectTCCmakeCalls);
+	at:'SUBPROJECT_MINGWMAKE_CALLS' put:(self subProjectMingwmakeCalls);
+	yourself
 
     "Created: / 17-08-2006 / 21:41:56 / cg"
     "Modified: / 05-09-2012 / 19:45:36 / cg"
@@ -4058,12 +4058,12 @@
 
     mappings := Dictionary new.
     ^ mappings
-        at:'APPLICATION' put:(self perform:#applicationName ifNotUnderstood:[self packageName]);
-        at:'APPLICATION_PACKAGE' put:self package printString;
-        at:'PREAMBLE' put:self builder_baseline_dot_rbspec_preamble;
-        at:'POSTAMBLE' put:self builder_baseline_dot_rbspec_postamble;
-        at:'PACKAGES' put:self builder_baseline_dot_rbspec_packages;
-        yourself.
+	at:'APPLICATION' put:(self perform:#applicationName ifNotUnderstood:[self packageName]);
+	at:'APPLICATION_PACKAGE' put:self package printString;
+	at:'PREAMBLE' put:self builder_baseline_dot_rbspec_preamble;
+	at:'POSTAMBLE' put:self builder_baseline_dot_rbspec_postamble;
+	at:'PACKAGES' put:self builder_baseline_dot_rbspec_packages;
+	yourself.
 
     "Modified: / 21-12-2010 / 11:00:22 / cg"
     "Created: / 24-02-2011 / 11:58:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4072,9 +4072,9 @@
 
 builder_baseline_dot_rbspec_packages
     ^ String streamContents:[:s |
-        self allPreRequisitesSorted do: [:packageId |
-            s nextPutLine:('  package "%1"' bindWith:packageId).
-        ] 
+	self allPreRequisitesSorted do: [:packageId |
+	    s nextPutLine:('  package "%1"' bindWith:packageId).
+	]
     ].
 
     "Created: / 24-02-2011 / 11:59:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4083,8 +4083,8 @@
 
 classLine_mappings:aClassName
     ^ Dictionary new
-        at:'CLASS' put:(self st2c:aClassName);
-        yourself
+	at:'CLASS' put:(self st2c:aClassName);
+	yourself
 
     "Modified: / 09-08-2006 / 18:27:07 / fm"
     "Created: / 19-09-2006 / 22:47:43 / cg"
@@ -4092,43 +4092,43 @@
 
 common_mappings
     ^ Dictionary new
-        at: 'TAB' put: ( Character tab asString );
-        at: 'TOP' put: ( 'depends-on-file(unix vs. win32)' );       "/ must be in specific mapping
-        at: 'LIBRARY_NAME' put: ( self libraryName );
-        at: 'SUBDIRECTORIES' put: (self generateSubDirectories);
-        at: 'MODULE' put: ( self module );
-        at: 'MODULE_DIRECTORY' put: ( self moduleDirectory );           "/ always unix format
-        at: 'MODULE_PATH' put: ( 'depends-on-file(unix vs. win32)' );   "/ must be in specific mapping
-        yourself
+	at: 'TAB' put: ( Character tab asString );
+	at: 'TOP' put: ( 'depends-on-file(unix vs. win32)' );       "/ must be in specific mapping
+	at: 'LIBRARY_NAME' put: ( self libraryName );
+	at: 'SUBDIRECTORIES' put: (self generateSubDirectories);
+	at: 'MODULE' put: ( self module );
+	at: 'MODULE_DIRECTORY' put: ( self moduleDirectory );           "/ always unix format
+	at: 'MODULE_PATH' put: ( 'depends-on-file(unix vs. win32)' );   "/ must be in specific mapping
+	yourself
 
     "Created: / 04-09-2012 / 13:04:26 / cg"
 !
 
 make_dot_proto_mappings
     ^ self common_mappings
-        at: 'MODULE' put: ( self module );
-        at: 'MODULE_DIRECTORY' put: ( self moduleDirectory );
-        at: 'MODULE_PATH' put: ( self moduleDirectory );
-        at: 'TOP' put: ( self pathToTopWithSeparator:'/' );
-        at: 'SUBDIRECTORIES' put: (self generateSubDirectories);
-        at: 'LIBRARY_NAME' put: ( self libraryName );
-        at: 'LOCAL_INCLUDES' put: (self generateLocalIncludes_unix);
-        at: 'LOCAL_DEFINES' put: self localDefines_unix;
-        at: 'GLOBAL_DEFINES' put: self globalDefines_unix;
-        at: 'COMMONSYMFLAG' put: (self commonSymbolsFlag);
-        at: 'HEADEROUTPUTARG' put: (self headerFileOutputArg);
-        at: 'PRIMARY_TARGET' put: (self primaryTarget_make_dot_proto);
-        at: 'ADDITIONAL_DEFINITIONS' put: (self additionalDefinitions_make_dot_proto);
-        at: 'ADDITIONAL_HEADERRULES' put: (self additionalHeaderRules_make_dot_proto);
-        at: 'ADDITIONAL_RULES' put: (self additionalRulesFor: 'Make.proto');
-        at: 'ADDITIONAL_RULES_SVN' put: (self additionalRulesSvn_make_dot_proto);
-        at: 'ADDITIONAL_RULES_HG' put: (self additionalRulesHG_make_dot_proto);
-        at: 'ADDITIONAL_TARGETS' put: (self additionalTargets_make_dot_proto);
-        at: 'ADDITIONAL_TARGETS_SVN' put: (self additionalTargetsSvn_make_dot_proto);
-        at: 'ADDITIONAL_LINK_LIBRARIES' put: (self additionalLinkLibraries_make_dot_proto);
-        at: 'ADDITIONAL_SHARED_LINK_LIBRARIES' put: (self additionalSharedLinkLibraries_make_dot_proto);
-        at: 'DEPENDENCIES' put: (self generateDependencies_unix);
-        yourself
+	at: 'MODULE' put: ( self module );
+	at: 'MODULE_DIRECTORY' put: ( self moduleDirectory );
+	at: 'MODULE_PATH' put: ( self moduleDirectory );
+	at: 'TOP' put: ( self pathToTopWithSeparator:'/' );
+	at: 'SUBDIRECTORIES' put: (self generateSubDirectories);
+	at: 'LIBRARY_NAME' put: ( self libraryName );
+	at: 'LOCAL_INCLUDES' put: (self generateLocalIncludes_unix);
+	at: 'LOCAL_DEFINES' put: self localDefines_unix;
+	at: 'GLOBAL_DEFINES' put: self globalDefines_unix;
+	at: 'COMMONSYMFLAG' put: (self commonSymbolsFlag);
+	at: 'HEADEROUTPUTARG' put: (self headerFileOutputArg);
+	at: 'PRIMARY_TARGET' put: (self primaryTarget_make_dot_proto);
+	at: 'ADDITIONAL_DEFINITIONS' put: (self additionalDefinitions_make_dot_proto);
+	at: 'ADDITIONAL_HEADERRULES' put: (self additionalHeaderRules_make_dot_proto);
+	at: 'ADDITIONAL_RULES' put: (self additionalRulesFor: 'Make.proto');
+	at: 'ADDITIONAL_RULES_SVN' put: (self additionalRulesSvn_make_dot_proto);
+	at: 'ADDITIONAL_RULES_HG' put: (self additionalRulesHG_make_dot_proto);
+	at: 'ADDITIONAL_TARGETS' put: (self additionalTargets_make_dot_proto);
+	at: 'ADDITIONAL_TARGETS_SVN' put: (self additionalTargetsSvn_make_dot_proto);
+	at: 'ADDITIONAL_LINK_LIBRARIES' put: (self additionalLinkLibraries_make_dot_proto);
+	at: 'ADDITIONAL_SHARED_LINK_LIBRARIES' put: (self additionalSharedLinkLibraries_make_dot_proto);
+	at: 'DEPENDENCIES' put: (self generateDependencies_unix);
+	yourself
 
     "Created: / 09-08-2006 / 11:20:45 / fm"
     "Modified: / 09-08-2006 / 16:44:48 / fm"
@@ -4139,12 +4139,12 @@
 
 make_dot_spec_mappings
     ^ self common_mappings
-        at: 'MODULE_DIRECTORY' put: ( self moduleDirectory );
-        at: 'STCWARNINGOPTIONS' put: (self stcWarningOptions);
-        at: 'STCOPTIMIZATIONOPTIONS' put: (self stcOptimizationOptions);
-        at: 'CLASSES' put: [self generateClasses_make_dot_spec];
-        at: 'OBJECTS' put: [self generateObjects_make_dot_spec];
-        yourself
+	at: 'MODULE_DIRECTORY' put: ( self moduleDirectory );
+	at: 'STCWARNINGOPTIONS' put: (self stcWarningOptions);
+	at: 'STCOPTIMIZATIONOPTIONS' put: (self stcOptimizationOptions);
+	at: 'CLASSES' put: [self generateClasses_make_dot_spec];
+	at: 'OBJECTS' put: [self generateObjects_make_dot_spec];
+	yourself
 
     "Created: / 18-08-2006 / 11:44:23 / cg"
     "Modified: / 05-09-2012 / 10:11:02 / cg"
@@ -4152,7 +4152,7 @@
 
 makefile_mappings
     ^ Dictionary new
-        yourself
+	yourself
 !
 
 packageName_dot_rc_mappings
@@ -4160,56 +4160,56 @@
 
     d := Dictionary new.
     d
-        at: 'PRODUCT_NAME' put: (self productName);
-        at: 'PRODUCT_VERSION' put: (self productVersion);
-        at: 'PRODUCT_DATE' put: (self productDate);
-        at: 'FILETYPE' put: ( 'VFT_DLL' );
-        at: 'FILE_VERSION_COMMASEPARATED' put: (self fileVersionCommaSeparated);
-        at: 'PRODUCT_VERSION_COMMASEPARATED' put: (self productVersionCommaSeparated);
-
-        at: 'COMPANY_NAME' put: (self companyName);
-        at: 'FILE_DESCRIPTION' put: (self fileDescription);
-        at: 'FILE_VERSION' put: (self fileVersion);
-        at: 'INTERNAL_NAME' put: (self internalName).
+	at: 'PRODUCT_NAME' put: (self productName);
+	at: 'PRODUCT_VERSION' put: (self productVersion);
+	at: 'PRODUCT_DATE' put: (self productDate);
+	at: 'FILETYPE' put: ( 'VFT_DLL' );
+	at: 'FILE_VERSION_COMMASEPARATED' put: (self fileVersionCommaSeparated);
+	at: 'PRODUCT_VERSION_COMMASEPARATED' put: (self productVersionCommaSeparated);
+
+	at: 'COMPANY_NAME' put: (self companyName);
+	at: 'FILE_DESCRIPTION' put: (self fileDescription);
+	at: 'FILE_VERSION' put: (self fileVersion);
+	at: 'INTERNAL_NAME' put: (self internalName).
 
     s := self legalCopyright.
     s notNil ifTrue:[
-        d at: 'LEGAL_COPYRIGHT_LINE' put: '      VALUE "LegalCopyright", "',s,'\0"'
+	d at: 'LEGAL_COPYRIGHT_LINE' put: '      VALUE "LegalCopyright", "',s,'\0"'
     ].
     s := String streamContents:[:stream|
-            |suff|
-
-            s := self applicationIconFileNameWindows.
-            s notNil ifTrue:[
-                s asFilename suffix isEmptyOrNil ifTrue:[
-                    suff := '.ico'
-                ] ifFalse:[
-                    suff := ''
-                ].
-                'IDR_MAINFRAME           ICON    DISCARDABLE     "%1%2"'
-                        expandPlaceholdersWith:(Array with:s with:suff) on:stream.
-                stream cr.
-            ].
-
-            s := self splashFileName.
-            s notNil ifTrue:[
-                s asFilename suffix isEmptyOrNil ifTrue:[
-                    suff := '.bmp'
-                ] ifFalse:[
-                    suff := ''
-                ].
-                'IDR_SPLASH           BITMAP    DISCARDABLE     "%1%2"'
-                        expandPlaceholdersWith:(Array with:s with:suff) on:stream.
-                stream cr.
-            ].
-            resourceCount := 2.
-            self applicationAdditionalIconFileNames do:[:eachFilename|
-                'IDR_MAINFRAME+%1           ICON    DISCARDABLE     "%2"'
-                        expandPlaceholdersWith:(Array with:resourceCount with:eachFilename) on:stream.
-                stream cr.
-                resourceCount := resourceCount+1.
-            ].
-        ].
+	    |suff|
+
+	    s := self applicationIconFileNameWindows.
+	    s notNil ifTrue:[
+		s asFilename suffix isEmptyOrNil ifTrue:[
+		    suff := '.ico'
+		] ifFalse:[
+		    suff := ''
+		].
+		'IDR_MAINFRAME           ICON    DISCARDABLE     "%1%2"'
+			expandPlaceholdersWith:(Array with:s with:suff) on:stream.
+		stream cr.
+	    ].
+
+	    s := self splashFileName.
+	    s notNil ifTrue:[
+		s asFilename suffix isEmptyOrNil ifTrue:[
+		    suff := '.bmp'
+		] ifFalse:[
+		    suff := ''
+		].
+		'IDR_SPLASH           BITMAP    DISCARDABLE     "%1%2"'
+			expandPlaceholdersWith:(Array with:s with:suff) on:stream.
+		stream cr.
+	    ].
+	    resourceCount := 2.
+	    self applicationAdditionalIconFileNames do:[:eachFilename|
+		'IDR_MAINFRAME+%1           ICON    DISCARDABLE     "%2"'
+			expandPlaceholdersWith:(Array with:resourceCount with:eachFilename) on:stream.
+		stream cr.
+		resourceCount := resourceCount+1.
+	    ].
+	].
     d at: #'ICONDEFINITION_LINE' put:s.
 
     ^ d
@@ -4222,28 +4222,28 @@
     |dependencies|
 
     dependencies := String
-            streamContents:[:s |
-                self allPreRequisites do:[:package |
-                    (self preRequisitesFor:package) do:[:prereq |
-                        s
-                            nextPutAll:('task "%1" => "%2"' bindWith:package with:prereq);
-                            cr
-                    ].
-                    s cr
-                ].
-                self effectivePreRequisites do:[:prereq |
-                    s
-                        nextPutAll:('task "%1" => "%2"' bindWith:self package with:prereq);
-                        cr
-                ].
-            ].
+	    streamContents:[:s |
+		self allPreRequisites do:[:package |
+		    (self preRequisitesFor:package) do:[:prereq |
+			s
+			    nextPutAll:('task "%1" => "%2"' bindWith:package with:prereq);
+			    cr
+		    ].
+		    s cr
+		].
+		self effectivePreRequisites do:[:prereq |
+		    s
+			nextPutAll:('task "%1" => "%2"' bindWith:self package with:prereq);
+			cr
+		].
+	    ].
 
     ^ (Dictionary new)
-        at:'DEPENDENCIES' put:dependencies;
-        yourself
-
-    "
-        stx_libjava generate_package_dot_deps_dot_rake
+	at:'DEPENDENCIES' put:dependencies;
+	yourself
+
+    "
+	stx_libjava generate_package_dot_deps_dot_rake
     "
 
     "Created: / 24-02-2011 / 22:32:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4263,16 +4263,16 @@
 !
 
 st2c:aString
-        ^ (aString asString
-            copyReplaceString:'_' withString:('_',($_ codePoint printStringRadix:8)))
-                replaceAny:':' with:$_
+	^ (aString asString
+	    copyReplaceString:'_' withString:('_',($_ codePoint printStringRadix:8)))
+		replaceAny:':' with:$_
 ! !
 
 !ProjectDefinition class methodsFor:'file mappings support'!
 
 classNamesByCategory
     "answer a dictionary
-        category -> classNames topological sorted"
+	category -> classNames topological sorted"
 
     |classes classNames mapping alreadyWarned|
 
@@ -4281,40 +4281,40 @@
     classes := Class classesSortedByLoadOrder:self compiled_classes_common.
     classNames := classes collect:[:eachClass| eachClass name].
     self namesAndAttributesIn:(self additionalClassNamesAndAttributes) do: [:nm :attr |
-        (attr isEmptyOrNil or:[(attr includes:#autoload) not]) ifTrue:[
-            classNames add:nm.
-        ].
+	(attr isEmptyOrNil or:[(attr includes:#autoload) not]) ifTrue:[
+	    classNames add:nm.
+	].
     ].
     mapping at:'COMMON' put:classNames.
 
     alreadyWarned := false.
     OperatingSystem knownPlatformNames do:[:platformID |
-        |platformClasses platformClassNames|
-
-        platformClasses := self compiled_classesForPlatform:platformID.
-        platformClasses notEmpty ifTrue:[
-            (platformClasses contains:[:each| each isNil or:[each isLoaded not]]) ifTrue:[
-                "win32 classes are not present in linux..."
-                Transcript show:'Missing classes for platform: '. Transcript showCR:platformID.
-                platformClassNames := self compiled_classNamesForPlatform:platformID.
-                platformClassNames
-                    select:[:nm | |cls| cls := Smalltalk classNamed:nm. cls isNil or:[cls isLoaded not]]
-                    thenDo:[:nm | Transcript tab; showCR:nm].
-                UserPreferences current suppressProjectDefinitionWarnings ifFalse:[
-                    alreadyWarned ifFalse:[
-                        (Dialog confirm:('Dependencies (and therefore build-order) might be incorrect\(some classes for platform ''%1'' are not present or autoloaded; see Transcript).\\Continue anyway without recomputing the compilation order for this platform''s classes?' withCRs bindWith:platformID))
-                        ifFalse:[
-                            AbortOperationRequest raise.
-                        ].
-                    ].
-                    alreadyWarned := true
-                ].
-            ] ifFalse:[
-                classes := Class classesSortedByLoadOrder:platformClasses.
-                platformClassNames := platformClasses collect:[:eachClass| eachClass name].
-            ].
-            mapping at:platformID asUppercase put:platformClassNames.
-        ].
+	|platformClasses platformClassNames|
+
+	platformClasses := self compiled_classesForPlatform:platformID.
+	platformClasses notEmpty ifTrue:[
+	    (platformClasses contains:[:each| each isNil or:[each isLoaded not]]) ifTrue:[
+		"win32 classes are not present in linux..."
+		Transcript show:'Missing classes for platform: '. Transcript showCR:platformID.
+		platformClassNames := self compiled_classNamesForPlatform:platformID.
+		platformClassNames
+		    select:[:nm | |cls| cls := Smalltalk classNamed:nm. cls isNil or:[cls isLoaded not]]
+		    thenDo:[:nm | Transcript tab; showCR:nm].
+		UserPreferences current suppressProjectDefinitionWarnings ifFalse:[
+		    alreadyWarned ifFalse:[
+			(Dialog confirm:('Dependencies (and therefore build-order) might be incorrect\(some classes for platform ''%1'' are not present or autoloaded; see Transcript).\\Continue anyway without recomputing the compilation order for this platform''s classes?' withCRs bindWith:platformID))
+			ifFalse:[
+			    AbortOperationRequest raise.
+			].
+		    ].
+		    alreadyWarned := true
+		].
+	    ] ifFalse:[
+		classes := Class classesSortedByLoadOrder:platformClasses.
+		platformClassNames := platformClasses collect:[:eachClass| eachClass name].
+	    ].
+	    mapping at:platformID asUppercase put:platformClassNames.
+	].
     ].
     ^ mapping
 
@@ -4355,8 +4355,8 @@
     ^ Smalltalk fileNameForClass:classNameOrClass.
 
     "
-        self filenameForClass:HTML::Encoder
-        Smalltalk fileNameForClass:HTML::Encoder
+	self filenameForClass:HTML::Encoder
+	Smalltalk fileNameForClass:HTML::Encoder
     "
 
     "Created: / 08-08-2006 / 20:17:28 / fm"
@@ -4379,56 +4379,56 @@
     "for the init-file: generate class-init-lines for a collection of classes"
 
     ^ String
-        streamContents:[:s |
-            |classesLoaded classNamesUnloaded classNamesSorted putLineForClassName|
-
-            putLineForClassName := 
-                [:className |
-                    |newClassLine mappings|
-
-                    mappings := self classLine_mappings:className.
-                    newClassLine := self replaceMappings:mappings in:classLineTemplate.
-                    s nextPutLine:newClassLine
-                ].
-            classesLoaded := classNames collect:[:eachClassName | Smalltalk classNamed:eachClassName]
-                                        thenSelect:[:eachClass | eachClass notNil and:[eachClass isLoaded]].
-            classNamesUnloaded := classNames
-                        select:[:nm |
-                            |cls|
-
-                            cls := Smalltalk classNamed:nm.
-                            cls isNil or:[ cls isLoaded not ]
-                        ].
-            classNamesSorted := (Class classesSortedByLoadOrder:classesLoaded) collect:[:cls | cls name].
-            classNamesSorted do:putLineForClassName.
-            classNamesUnloaded do:putLineForClassName.
-
-            includeAdditionalClasses ifTrue:[
-                self namesAndAttributesIn:(self additionalClassNamesAndAttributes)
-                    do:[:nm :attr |
-                        (attr isEmptyOrNil or:[ (attr includes:#autoload) not ]) ifTrue:[
-                            putLineForClassName value:nm.
-                        ].
-                    ].
-                #( ('UNIX' unix)
-                   ('WIN32' win32)
-                   ('OSX' osx)
-                   ('VMS' vms)
-                   ('BEOS' beos) )
-                        pairsDo:[:ifdef :platformName |
-                            |archClassNames archClassesLoaded|
-
-                            archClassNames := self compiled_classNamesForPlatform:platformName.
-                            archClassNames notEmpty ifTrue:[
-                                s nextPutLine:'#ifdef ' , ifdef.
-                                archClassNames do:[:clsName |
-                                    putLineForClassName value:clsName
-                                ].
-                                s nextPutLine:'#endif /* ' , ifdef , ' */'.
-                            ].
-                        ].
-            ]
-        ]
+	streamContents:[:s |
+	    |classesLoaded classNamesUnloaded classNamesSorted putLineForClassName|
+
+	    putLineForClassName :=
+		[:className |
+		    |newClassLine mappings|
+
+		    mappings := self classLine_mappings:className.
+		    newClassLine := self replaceMappings:mappings in:classLineTemplate.
+		    s nextPutLine:newClassLine
+		].
+	    classesLoaded := classNames collect:[:eachClassName | Smalltalk classNamed:eachClassName]
+					thenSelect:[:eachClass | eachClass notNil and:[eachClass isLoaded]].
+	    classNamesUnloaded := classNames
+			select:[:nm |
+			    |cls|
+
+			    cls := Smalltalk classNamed:nm.
+			    cls isNil or:[ cls isLoaded not ]
+			].
+	    classNamesSorted := (Class classesSortedByLoadOrder:classesLoaded) collect:[:cls | cls name].
+	    classNamesSorted do:putLineForClassName.
+	    classNamesUnloaded do:putLineForClassName.
+
+	    includeAdditionalClasses ifTrue:[
+		self namesAndAttributesIn:(self additionalClassNamesAndAttributes)
+		    do:[:nm :attr |
+			(attr isEmptyOrNil or:[ (attr includes:#autoload) not ]) ifTrue:[
+			    putLineForClassName value:nm.
+			].
+		    ].
+		#( ('UNIX' unix)
+		   ('WIN32' win32)
+		   ('OSX' osx)
+		   ('VMS' vms)
+		   ('BEOS' beos) )
+			pairsDo:[:ifdef :platformName |
+			    |archClassNames archClassesLoaded|
+
+			    archClassNames := self compiled_classNamesForPlatform:platformName.
+			    archClassNames notEmpty ifTrue:[
+				s nextPutLine:'#ifdef ' , ifdef.
+				archClassNames do:[:clsName |
+				    putLineForClassName value:clsName
+				].
+				s nextPutLine:'#endif /* ' , ifdef , ' */'.
+			    ].
+			].
+	    ]
+	]
 
     "
      bosch_dapasx_datenbasis  generateClassLines_libInit_dot_cc
@@ -4461,14 +4461,14 @@
     classNamesDict := self classNamesByCategory.
 
     ^ String streamContents:[:s |
-        classNamesDict keysAndValuesDo:[:eachCategory :classNames|
-            s nextPutLine:eachCategory,'_CLASSES= \'.
-            classNames do:[:eachClassName|
-                s tab; nextPutAll:eachClassName; nextPutLine:' \'.
-            ].
-            s cr.
-        ].
-        s cr.
+	classNamesDict keysAndValuesDo:[:eachCategory :classNames|
+	    s nextPutLine:eachCategory,'_CLASSES= \'.
+	    classNames do:[:eachClassName|
+		s tab; nextPutAll:eachClassName; nextPutLine:' \'.
+	    ].
+	    s cr.
+	].
+	s cr.
     ].
 
     "
@@ -4486,9 +4486,9 @@
     "for the init-file: generate a single class-init-line for the definition class itself"
 
     ^ self
-        generateClassLines:(self classLine_libInit_dot_cc)
-        forClasses:(Array with:self name)
-        includeAdditionalClasses:false
+	generateClassLines:(self classLine_libInit_dot_cc)
+	forClasses:(Array with:self name)
+	includeAdditionalClasses:false
 
     "
      stx_libbasic generateDefinitionClassLine_libInit_dot_cc
@@ -4497,162 +4497,162 @@
 
 generateDependencies:whichArchitecture
     ^ String
-        streamContents:[:s |
-            |classNames classesPresent classesLoaded clsBaseName putDependencyForClassBlock
-             putDependencyForClassBaseNameBlock
-             archClassNames archClassesPresent archClassesLoaded
-             putSingleClassDependencyEntryBlock putDependencyForExtensionsBlock classSortBlock|
-
-            classSortBlock := [ :a :b|
-                a package == b package ifTrue:[
-                    a name < b name
-                ] ifFalse:[
-                    a package < b package
-                ].
-            ].
-
-            putSingleClassDependencyEntryBlock := [:cls |
-                    |sclsBaseName|
-
-                    s nextPutAll:' $(INCLUDE_TOP)'.
-                    s nextPutAll:(self pathSeparator:whichArchitecture).
-                    sclsBaseName := self filenameForClass:cls.
-                    s nextPutAll:(self
-                                topRelativePathTo:sclsBaseName
-                                inPackage:cls package
-                                architecture:whichArchitecture).
-                    s nextPutAll:'.$(H)'.
-                ].
-
-            putDependencyForClassBaseNameBlock := [:clsBaseName |
-                    s nextPutAll:('$(OUTDIR)',clsBaseName,'.$(O)').
-                    s nextPutAll:' '.
-                    s nextPutAll:(clsBaseName,'.$(C)').
-                    s nextPutAll:' '.
-                    s nextPutAll:clsBaseName.
-                    s nextPutAll:'.$(H)'.
-                    s nextPutAll:': '.
-                    s nextPutAll:clsBaseName.
-                    s nextPutAll:'.st'.
-                ].
-
-
-            putDependencyForClassBlock := [:cls |
-                    |clsBaseName classes|
-
-                    clsBaseName := self filenameForClass:cls.
-                    putDependencyForClassBaseNameBlock value:clsBaseName.
-                    cls isLoaded ifTrue:[
-                        classes := IdentitySet new.
-                        cls
-                            sharedPools do:[:poolClass |
-                                poolClass isNil ifTrue:[
-                                    Dialog warn:'At least one pool class is missing.\\Dependencies are incomplete.' withCRs
-                                ] ifFalse:[
-                                    classes add:poolClass.
-                                ]
-                            ].
-
-                        cls
-                            allSuperclassesDo:[:scls |
-                                classes add:scls.
-                            ].
-                        cls
-                            allPrivateClassesDo:[:eachPrivateClass |
-                                eachPrivateClass
-                                    allSuperclassesDo:[:scls |
-                                        |sclsBaseName|
-
-                                        scls ~~ cls ifTrue:[
-                                            scls isPrivate ifFalse:[
-                                                (classes includes:scls) ifFalse:[
-                                                    classes add:scls.
-                                                ].
-                                            ].
-                                        ].
-                                    ]
-                            ].
-                        "/ Sort them to get stable order to avoid false conflicts
-                        classes := classes asSortedCollection:classSortBlock.
-                        classes do:[:each | putSingleClassDependencyEntryBlock value:each].
-                    ].
-                    s nextPutLine:' $(STCHDR)'.
-                ].
-
-            putDependencyForExtensionsBlock := [
-                    | classes |
-
-                    s nextPutAll:'$(OUTDIR)extensions.$(O): extensions.st'.
-                    classes := Set new.
-                    self extensionMethodNames pairWiseDo:[:className :selector |
-                            |mthdCls cls|
-
-                            ((mthdCls := Smalltalk classNamed:className) notNil
-                              and:[ mthdCls isLoaded ])
-                                    ifTrue:[
-                                        cls := mthdCls theNonMetaclass.
-                                        (classes includes:cls) ifFalse:[
-                                            cls
-                                                withAllSuperclassesDo:[:scls |
-                                                    (classes includes:scls) ifFalse:[
-                                                        classes add:scls.
-                                                    ].
-                                                ].
-                                        ].
-                                    ].
-                        ].
-                    "/ Sort them to get stable order to avoid false conflicts
-                    classes := classes asSortedCollection:classSortBlock.
-                    classes do:[:each | putSingleClassDependencyEntryBlock value:each].
-                    s nextPutLine:' $(STCHDR)'.
-                ].
-
-            classNames := self compiled_classNames_common.
-            classesPresent := classNames
-                collect:[:className | Smalltalk classNamed:className]
-                thenSelect:[:cls | cls notNil].
-            classesLoaded := classesPresent select:[:cls | cls isLoaded].
-
-            (Class classesSortedByLoadOrder:classesLoaded) do:putDependencyForClassBlock.
-            classesPresent reject:[:cls | cls isLoaded] thenDo:putDependencyForClassBlock.
-
-            self namesAndAttributesIn:(self additionalClassNamesAndAttributes)
-                do:[:className :attr |
-                    |cls|
-
-                    (attr isEmptyOrNil or:[ (attr includes:#autoload) not ]) ifTrue:[
-                        ((cls := Smalltalk classNamed:className) notNil) ifTrue:[
-                            putDependencyForClassBlock value:cls.
-                        ]
-                    ].
-                ].
-            archClassNames := self compiled_classNamesForPlatform:whichArchitecture.
-            archClassesPresent := archClassNames
-                collect:[:className | Smalltalk classNamed:className]
-                thenSelect:[:cls | cls notNil].
-
-            archClassesLoaded := archClassesPresent select:[:cls | cls isLoaded].
-
-            (Class classesSortedByLoadOrder:archClassesLoaded)
-                do:putDependencyForClassBlock.
-
-            "some classes are not loaded - probably this is the wrong architecture.
-             Sorry, but for these classes, we do not know the superclass chain"
-            archClassesPresent
-                select:[:cls | cls isLoaded not]
-                thenDo:putDependencyForClassBlock.
-
-            "for the following classes, we do not know the superclass chain
-             and neither the real class file name"
-            archClassNames
-                select:[:eachClassName | (Smalltalk classNamed:eachClassName) isNil]
-                thenDo:[:eachClassName |
-                    putDependencyForClassBaseNameBlock value:(self filenameForClass:eachClassName).
-                    s nextPutLine:' $(STCHDR)'.
-                ].
-
-            self hasExtensionMethods ifTrue:putDependencyForExtensionsBlock.
-        ]
+	streamContents:[:s |
+	    |classNames classesPresent classesLoaded clsBaseName putDependencyForClassBlock
+	     putDependencyForClassBaseNameBlock
+	     archClassNames archClassesPresent archClassesLoaded
+	     putSingleClassDependencyEntryBlock putDependencyForExtensionsBlock classSortBlock|
+
+	    classSortBlock := [ :a :b|
+		a package == b package ifTrue:[
+		    a name < b name
+		] ifFalse:[
+		    a package < b package
+		].
+	    ].
+
+	    putSingleClassDependencyEntryBlock := [:cls |
+		    |sclsBaseName|
+
+		    s nextPutAll:' $(INCLUDE_TOP)'.
+		    s nextPutAll:(self pathSeparator:whichArchitecture).
+		    sclsBaseName := self filenameForClass:cls.
+		    s nextPutAll:(self
+				topRelativePathTo:sclsBaseName
+				inPackage:cls package
+				architecture:whichArchitecture).
+		    s nextPutAll:'.$(H)'.
+		].
+
+	    putDependencyForClassBaseNameBlock := [:clsBaseName |
+		    s nextPutAll:('$(OUTDIR)',clsBaseName,'.$(O)').
+		    s nextPutAll:' '.
+		    s nextPutAll:(clsBaseName,'.$(C)').
+		    s nextPutAll:' '.
+		    s nextPutAll:clsBaseName.
+		    s nextPutAll:'.$(H)'.
+		    s nextPutAll:': '.
+		    s nextPutAll:clsBaseName.
+		    s nextPutAll:'.st'.
+		].
+
+
+	    putDependencyForClassBlock := [:cls |
+		    |clsBaseName classes|
+
+		    clsBaseName := self filenameForClass:cls.
+		    putDependencyForClassBaseNameBlock value:clsBaseName.
+		    cls isLoaded ifTrue:[
+			classes := IdentitySet new.
+			cls
+			    sharedPools do:[:poolClass |
+				poolClass isNil ifTrue:[
+				    Dialog warn:'At least one pool class is missing.\\Dependencies are incomplete.' withCRs
+				] ifFalse:[
+				    classes add:poolClass.
+				]
+			    ].
+
+			cls
+			    allSuperclassesDo:[:scls |
+				classes add:scls.
+			    ].
+			cls
+			    allPrivateClassesDo:[:eachPrivateClass |
+				eachPrivateClass
+				    allSuperclassesDo:[:scls |
+					|sclsBaseName|
+
+					scls ~~ cls ifTrue:[
+					    scls isPrivate ifFalse:[
+						(classes includes:scls) ifFalse:[
+						    classes add:scls.
+						].
+					    ].
+					].
+				    ]
+			    ].
+			"/ Sort them to get stable order to avoid false conflicts
+			classes := classes asSortedCollection:classSortBlock.
+			classes do:[:each | putSingleClassDependencyEntryBlock value:each].
+		    ].
+		    s nextPutLine:' $(STCHDR)'.
+		].
+
+	    putDependencyForExtensionsBlock := [
+		    | classes |
+
+		    s nextPutAll:'$(OUTDIR)extensions.$(O): extensions.st'.
+		    classes := Set new.
+		    self extensionMethodNames pairWiseDo:[:className :selector |
+			    |mthdCls cls|
+
+			    ((mthdCls := Smalltalk classNamed:className) notNil
+			      and:[ mthdCls isLoaded ])
+				    ifTrue:[
+					cls := mthdCls theNonMetaclass.
+					(classes includes:cls) ifFalse:[
+					    cls
+						withAllSuperclassesDo:[:scls |
+						    (classes includes:scls) ifFalse:[
+							classes add:scls.
+						    ].
+						].
+					].
+				    ].
+			].
+		    "/ Sort them to get stable order to avoid false conflicts
+		    classes := classes asSortedCollection:classSortBlock.
+		    classes do:[:each | putSingleClassDependencyEntryBlock value:each].
+		    s nextPutLine:' $(STCHDR)'.
+		].
+
+	    classNames := self compiled_classNames_common.
+	    classesPresent := classNames
+		collect:[:className | Smalltalk classNamed:className]
+		thenSelect:[:cls | cls notNil].
+	    classesLoaded := classesPresent select:[:cls | cls isLoaded].
+
+	    (Class classesSortedByLoadOrder:classesLoaded) do:putDependencyForClassBlock.
+	    classesPresent reject:[:cls | cls isLoaded] thenDo:putDependencyForClassBlock.
+
+	    self namesAndAttributesIn:(self additionalClassNamesAndAttributes)
+		do:[:className :attr |
+		    |cls|
+
+		    (attr isEmptyOrNil or:[ (attr includes:#autoload) not ]) ifTrue:[
+			((cls := Smalltalk classNamed:className) notNil) ifTrue:[
+			    putDependencyForClassBlock value:cls.
+			]
+		    ].
+		].
+	    archClassNames := self compiled_classNamesForPlatform:whichArchitecture.
+	    archClassesPresent := archClassNames
+		collect:[:className | Smalltalk classNamed:className]
+		thenSelect:[:cls | cls notNil].
+
+	    archClassesLoaded := archClassesPresent select:[:cls | cls isLoaded].
+
+	    (Class classesSortedByLoadOrder:archClassesLoaded)
+		do:putDependencyForClassBlock.
+
+	    "some classes are not loaded - probably this is the wrong architecture.
+	     Sorry, but for these classes, we do not know the superclass chain"
+	    archClassesPresent
+		select:[:cls | cls isLoaded not]
+		thenDo:putDependencyForClassBlock.
+
+	    "for the following classes, we do not know the superclass chain
+	     and neither the real class file name"
+	    archClassNames
+		select:[:eachClassName | (Smalltalk classNamed:eachClassName) isNil]
+		thenDo:[:eachClassName |
+		    putDependencyForClassBaseNameBlock value:(self filenameForClass:eachClassName).
+		    s nextPutLine:' $(STCHDR)'.
+		].
+
+	    self hasExtensionMethods ifTrue:putDependencyForExtensionsBlock.
+	]
 
     "
      stx_libbasic3 generateDependencies:#unix
@@ -4685,7 +4685,7 @@
     "for the init-file: generate a single external definition for a single class for the definition class itself"
 
     ^ self
-        generateClassLines:(self classExternalDeclarationLine_libInit_dot_cc)
+	generateClassLines:(self classExternalDeclarationLine_libInit_dot_cc)
 
     "
      stx_libbasic generateExternalDeclarationLines_libInit_dot_cc
@@ -4694,11 +4694,11 @@
 
 generateLocalIncludes_unix
     ^ String streamContents:[:s |
-        s nextPutAll:(self localIncludes_unix).
-        self searchForProjectsWhichProvideHeaderFiles asSortedCollection
-            do:[:includeProject |
-                s nextPutAll:' -I$(INCLUDE_TOP)/',(self topRelativePathToPackage:includeProject withSeparator:'/')
-            ]
+	s nextPutAll:(self localIncludes_unix).
+	self searchForProjectsWhichProvideHeaderFiles asSortedCollection
+	    do:[:includeProject |
+		s nextPutAll:' -I$(INCLUDE_TOP)/',(self topRelativePathToPackage:includeProject withSeparator:'/')
+	    ]
     ]
 
     "
@@ -4718,11 +4718,11 @@
 
 generateLocalIncludes_win32
     ^ String streamContents:[:s |
-        s nextPutAll:(self localIncludes_win32).
-        self searchForProjectsWhichProvideHeaderFiles asSortedCollection
-            do:[:includeProject |
-                s nextPutAll:' -I$(INCLUDE_TOP)\',(self topRelativePathToPackage:includeProject withSeparator:'\')
-            ]
+	s nextPutAll:(self localIncludes_win32).
+	self searchForProjectsWhichProvideHeaderFiles asSortedCollection
+	    do:[:includeProject |
+		s nextPutAll:' -I$(INCLUDE_TOP)\',(self topRelativePathToPackage:includeProject withSeparator:'\')
+	    ]
     ]
 
     "
@@ -4744,26 +4744,26 @@
     classNamesDict := self classNamesByCategory.
 
     ^ String streamContents:[:s |
-        |putLineForClassName|
-
-        putLineForClassName :=
-            [:eachClassName |
-                |mappings newObjectLine|
-                mappings := self objectLine_make_dot_spec_mappings: eachClassName.
-                newObjectLine := self replaceMappings: mappings in: self objectLine_make_dot_spec.
-                s nextPutLine:newObjectLine.
-            ].
-
-        classNamesDict keysAndValuesDo:[:eachCategory :classNames|
-            s nextPutLine:eachCategory,'_OBJS= \'.
-            classNames do:putLineForClassName.
-            (eachCategory = 'COMMON' and:[self hasExtensionMethods]) ifTrue:[
-                s nextPutLine:'    $(OUTDIR)extensions.$(O) \'.
-            ].
-
-            s cr.
-        ].
-        s cr.
+	|putLineForClassName|
+
+	putLineForClassName :=
+	    [:eachClassName |
+		|mappings newObjectLine|
+		mappings := self objectLine_make_dot_spec_mappings: eachClassName.
+		newObjectLine := self replaceMappings: mappings in: self objectLine_make_dot_spec.
+		s nextPutLine:newObjectLine.
+	    ].
+
+	classNamesDict keysAndValuesDo:[:eachCategory :classNames|
+	    s nextPutLine:eachCategory,'_OBJS= \'.
+	    classNames do:putLineForClassName.
+	    (eachCategory = 'COMMON' and:[self hasExtensionMethods]) ifTrue:[
+		s nextPutLine:'    $(OUTDIR)extensions.$(O) \'.
+	    ].
+
+	    s cr.
+	].
+	s cr.
     ].
 
     "
@@ -4781,22 +4781,22 @@
     |myProjectId|
 
     ^ String streamContents:[:s |
-        myProjectId := self package.
-        "Note: the trailing blank in 'CFLAGS_LOCAL=$(GLOBALDEFINES) '
-         is required!!
-         Use 'pushd' instead of 'cd', since cd is executed by borland make directly.
-         'popd' is not needed, since each line is executed in
-                an own cmd.exe process.
-         'popd' is not desireable, since it masks a possible
-                error return from the 'bmake'.
-        "
-
-        "cg: changed to not go and remake librun"
-        (self allPreRequisitesSorted:#effectiveMandatoryPreRequisites "#effectivePreRequisites") do:[:eachProjectId |
-            s tab; nextPutAll:'pushd ';
-                   nextPutAll:(self msdosPathToPackage:eachProjectId from:myProjectId);
-                   nextPutLine:' & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "'.
-        ].
+	myProjectId := self package.
+	"Note: the trailing blank in 'CFLAGS_LOCAL=$(GLOBALDEFINES) '
+	 is required!!
+	 Use 'pushd' instead of 'cd', since cd is executed by borland make directly.
+	 'popd' is not needed, since each line is executed in
+		an own cmd.exe process.
+	 'popd' is not desireable, since it masks a possible
+		error return from the 'bmake'.
+	"
+
+	"cg: changed to not go and remake librun"
+	(self allPreRequisitesSorted:#effectiveMandatoryPreRequisites "#effectivePreRequisites") do:[:eachProjectId |
+	    s tab; nextPutAll:'pushd ';
+		   nextPutAll:(self msdosPathToPackage:eachProjectId from:myProjectId);
+		   nextPutLine:' & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "'.
+	].
     ].
 
     "
@@ -4809,13 +4809,13 @@
     |libPath|
 
     ^ String streamContents:[:s |
-        "cg: changed to not go and remake librun"
-        (self allPreRequisitesSorted:#effectiveMandatoryPreRequisites "#effectivePreRequisites") do:[:projectID |
-            libPath := self pathToPackage:projectID withSeparator:'/'.
-            s tab; nextPutAll: 'cd ', libPath; nextPutLine:' && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES) "'.
-        ].
-
-        s cr.
+	"cg: changed to not go and remake librun"
+	(self allPreRequisitesSorted:#effectiveMandatoryPreRequisites "#effectivePreRequisites") do:[:projectID |
+	    libPath := self pathToPackage:projectID withSeparator:'/'.
+	    s tab; nextPutAll: 'cd ', libPath; nextPutLine:' && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES) "'.
+	].
+
+	s cr.
     ].
 
     "
@@ -4834,9 +4834,9 @@
      is required!!
      Use 'pushd' instead of 'cd', since cd is executed by borland make directly.
      'popd' is not needed, since each line is executed in
-            an own cmd.exe process.
+	    an own cmd.exe process.
      'popd' is not desierable, since it masks a possible
-            error return from the 'bmake'.
+	    error return from the 'bmake'.
     "
 
     preRequisites := self allPreRequisitesSorted:#effectivePreRequisites.
@@ -4844,11 +4844,11 @@
     preRequisites removeAllFoundIn:(self allPreRequisites:#mandatoryPreRequisites).
 
     ^ String streamContents:[:s |
-        preRequisites do:[:eachProjectId |
-            s tab; nextPutAll:'pushd ';
-                   nextPutAll:(self msdosPathToPackage:eachProjectId from:myProjectId);
-                   nextPutLine:' & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "'.
-        ].
+	preRequisites do:[:eachProjectId |
+	    s tab; nextPutAll:'pushd ';
+		   nextPutAll:(self msdosPathToPackage:eachProjectId from:myProjectId);
+		   nextPutLine:' & $(MAKE_BAT) "CFLAGS_LOCAL=$(GLOBALDEFINES) "'.
+	].
     ].
 
     "
@@ -4865,12 +4865,12 @@
     preRequisites removeAllFoundIn:(self allPreRequisites:#mandatoryPreRequisites).
 
     ^ String streamContents:[:s |
-        preRequisites do:[:projectID |
-            libPath := self pathToPackage:projectID withSeparator:'/'.
-            s tab; nextPutAll: 'cd ', libPath; nextPutLine:' && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES) "'.
-        ].
-
-        s cr.
+	preRequisites do:[:projectID |
+	    libPath := self pathToPackage:projectID withSeparator:'/'.
+	    s tab; nextPutAll: 'cd ', libPath; nextPutLine:' && $(MAKE) "CFLAGS_LOCAL=$(GLOBALDEFINES) "'.
+	].
+
+	s cr.
     ].
 
     "
@@ -4883,10 +4883,10 @@
 
 generateSubDirectories
     ^ String streamContents:[:s |
-        self subProjects
-            do:[:eachProjectID |
-                s space; nextPutAll:(self pathToPackage:eachProjectID from:self package withSeparator:'/')
-            ]
+	self subProjects
+	    do:[:eachProjectID |
+		s space; nextPutAll:(self pathToPackage:eachProjectID from:self package withSeparator:'/')
+	    ]
     ]
 
     "
@@ -4901,9 +4901,9 @@
     "for the init-file: generate a single class-init-line for the definition class itself"
 
     ^ self
-        generateClassLines:(self classLine_libInit_dot_cc)
-        forClasses:(Array with:self name)
-        includeAdditionalClasses:false
+	generateClassLines:(self classLine_libInit_dot_cc)
+	forClasses:(Array with:self name)
+	includeAdditionalClasses:false
 
     "
      stx_libbasic generate_definitionClassLine_libInit_dot_cc
@@ -4918,8 +4918,8 @@
 
 objectLine_make_dot_spec_mappings: aClassName
     ^ Dictionary new
-        at: 'CLASSFILE' put:(self filenameForClass:aClassName);
-        yourself
+	at: 'CLASSFILE' put:(self filenameForClass:aClassName);
+	yourself
 
     "Created: / 08-08-2006 / 20:17:28 / fm"
     "Modified: / 09-08-2006 / 18:26:52 / fm"
@@ -4942,30 +4942,30 @@
 
 subProjectMakeCallsUsing:callString
     "for xxxmake.bat files"
-    
+
     ^ String streamContents:[:s |
-        (self effectiveSubProjects:#win32) do:[:packageID |
-            |pkgLabel skipLabel joinLabel|
-            
-            pkgLabel := (packageID copyReplaceAll:$: with:$_) copyReplaceAll:$/ with:$_.
-            skipLabel := 'skip_',pkgLabel.
-            joinLabel := 'done_',pkgLabel.
-            s nextPutLine:'@if not exist ',(self msdosPathToPackage:packageID from:(self package)),' goto ',skipLabel.
-            s nextPutLine:'@echo "***********************************"'.
-            s nextPutLine:'@echo "Building ',(packageID copyReplaceAll:$: with:$/),'"'.
-            s nextPutLine:'@echo "***********************************"'.
-            s nextPutLine:'@pushd ', (self msdosPathToPackage:packageID from:(self package)).
-            s nextPutAll:'@'; nextPutAll:callString; nextPutLine:' || exit /b "%errorlevel%"'.
-            s nextPutLine:'@popd'.
-            s nextPutLine:'@goto ',joinLabel.
-            s nextPutLine:':',skipLabel.
-            s nextPutLine:'@echo "###################################"'.
-            s nextPutLine:'@echo "FOLDER MISSING: ',(packageID copyReplaceAll:$: with:$/),'"'.
-            s nextPutLine:'@echo "###################################"'.
-            s nextPutLine:'exit /b 1'.
-            s nextPutLine:':',joinLabel.
-            s cr.
-        ]
+	(self effectiveSubProjects:#win32) do:[:packageID |
+	    |pkgLabel skipLabel joinLabel|
+
+	    pkgLabel := (packageID copyReplaceAll:$: with:$_) copyReplaceAll:$/ with:$_.
+	    skipLabel := 'skip_',pkgLabel.
+	    joinLabel := 'done_',pkgLabel.
+	    s nextPutLine:'@if not exist ',(self msdosPathToPackage:packageID from:(self package)),' goto ',skipLabel.
+	    s nextPutLine:'@echo "***********************************"'.
+	    s nextPutLine:'@echo "Building ',(packageID copyReplaceAll:$: with:$/),'"'.
+	    s nextPutLine:'@echo "***********************************"'.
+	    s nextPutLine:'@pushd ', (self msdosPathToPackage:packageID from:(self package)).
+	    s nextPutAll:'@'; nextPutAll:callString; nextPutLine:' || exit /b "%errorlevel%"'.
+	    s nextPutLine:'@popd'.
+	    s nextPutLine:'@goto ',joinLabel.
+	    s nextPutLine:':',skipLabel.
+	    s nextPutLine:'@echo "###################################"'.
+	    s nextPutLine:'@echo "FOLDER MISSING: ',(packageID copyReplaceAll:$: with:$/),'"'.
+	    s nextPutLine:'@echo "###################################"'.
+	    s nextPutLine:'exit /b 1'.
+	    s nextPutLine:':',joinLabel.
+	    s cr.
+	]
     ]
 
     "Created: / 14-09-2006 / 18:40:09 / cg"
@@ -5168,15 +5168,15 @@
 
 generate_osx_info_dot_plist
     "template for the info.plist file, which is included in an OS X deployment"
-    
+
     |plist|
 
     (plist := self osx_info_dot_plist_dictionary) isNil ifTrue:[^ nil].
     MacPlistXMLCoder isNil ifTrue:[
-        Smalltalk loadPackage:'stx:goodies/xml/stx'.
-        Smalltalk loadPackage:'stx:goodies/fileformats/plist'.
-    ].    
-    ^ MacPlistXMLCoder encode:plist     
+	Smalltalk loadPackage:'stx:goodies/xml/stx'.
+	Smalltalk loadPackage:'stx:goodies/fileformats/plist'.
+    ].
+    ^ MacPlistXMLCoder encode:plist
 
     "
      exept_expecco_application info_dot_plist
@@ -5293,7 +5293,7 @@
 .PHONY: run
 
 run: makefile
-        $(MAKE) -f makefile
+	$(MAKE) -f makefile
 
 #only needed for the definition of $(TOP)
 include Make.proto
@@ -5301,7 +5301,7 @@
 makefile: mf
 
 mf:
-        $(TOP)/rules/stmkmf
+	$(TOP)/rules/stmkmf
 '
 !
 
@@ -5340,45 +5340,45 @@
 
 osx_info_dot_plist_dictionary
     "template for the info.plist file, which is included in an OS X deployment"
-    
+
     |plist pkg icnFilename docTypeDescriptions|
-    
+
     plist := Dictionary new.
     plist at:'CFBundleInfoDictionaryVersion' put:'6.0'.
     pkg := self package copyReplaceAny:':/' with:$..
     (pkg endsWith:'.application') ifTrue:[
-        pkg := pkg copyButLast:'.application' size.
-    ].    
+	pkg := pkg copyButLast:'.application' size.
+    ].
     plist at:'CFBundleIdentifier' put:pkg.
     plist at:'CFBundleShortVersionString' put:(self fileVersion asString).
     plist at:'CFBundleVersion' put:(self fileVersion asString).
     plist at:'LSMinimumSystemVersion' put:'10.6'.
     "/ plist at:'CFBundleDevelopmentRegion' put:'English'.
     plist at:'CFBundleExecutable' put:(self applicationName).
-    
+
     self isLibraryDefinition ifTrue:[
-        plist at:'CFBundleName' put:(self package copyReplaceAny:':/' with:$.).
+	plist at:'CFBundleName' put:(self package copyReplaceAny:':/' with:$.).
     ] ifFalse:[
-        plist at:'CFBundleName' put:(self applicationName).
-        plist at:'CFBundlePackageType' put:'APPL'.
-    ].
-    
-    (icnFilename := self applicationIconFileNameOSX) notNil ifTrue:[    
-        plist at:'CFBundleIconFile' put:icnFilename.
+	plist at:'CFBundleName' put:(self applicationName).
+	plist at:'CFBundlePackageType' put:'APPL'.
+    ].
+
+    (icnFilename := self applicationIconFileNameOSX) notNil ifTrue:[
+	plist at:'CFBundleIconFile' put:icnFilename.
     ].
     (docTypeDescriptions := self applicationDocumentTypeDescriptions) notNil ifTrue:[
-        plist at:'CFBundleDocumentTypes' put:
-            (docTypeDescriptions collect:[:each |
-                |d|
-                d := Dictionary new.
-                d at:'CFBundleTypeExtensions' put:{ each extension }.
-                d at:'CFBundleTypeIconFile' put:{ each iconFileOSX }.
-                d at:'CFBundleTypeMimeTypes' put:{ each mimeType }.
-                d at:'CFBundleTypeName' put:(each documentTypeName).
-                d at:'CFBundleTypeRole' put:'Editor'.
-                d
-            ]).
-    ].        
+	plist at:'CFBundleDocumentTypes' put:
+	    (docTypeDescriptions collect:[:each |
+		|d|
+		d := Dictionary new.
+		d at:'CFBundleTypeExtensions' put:{ each extension }.
+		d at:'CFBundleTypeIconFile' put:{ each iconFileOSX }.
+		d at:'CFBundleTypeMimeTypes' put:{ each mimeType }.
+		d at:'CFBundleTypeName' put:(each documentTypeName).
+		d at:'CFBundleTypeRole' put:'Editor'.
+		d
+	    ]).
+    ].
     ^ plist
 
     "
@@ -5507,7 +5507,7 @@
     "raise an error, if the package is not suitable for loading"
 
     self supportedOnPlatform ifFalse:[
-        PackageNotCompatibleError raiseWith:self package.
+	PackageNotCompatibleError raiseWith:self package.
     ].
 
     "Modified (comment): / 24-02-2017 / 10:06:44 / cg"
@@ -5522,14 +5522,14 @@
     self supportedOnPlatform ifFalse:[^ self].
 
     self hasAllExtensionsLoaded ifFalse:[
-        self breakPoint:#cg.
+	self breakPoint:#cg.
     ].
     self hasAllClassesFullyLoaded ifFalse:[
-        self hasAllClassesLoaded ifFalse:[
-            self breakPoint:#cg.
-        ].
-        self installAutoloadedClasses.
-        self classes do:[:cls | cls autoload ].
+	self hasAllClassesLoaded ifFalse:[
+	    self breakPoint:#cg.
+	].
+	self installAutoloadedClasses.
+	self classes do:[:cls | cls autoload ].
     ].
 
     "
@@ -5564,16 +5564,16 @@
     self supportedOnPlatform ifFalse:[^ false].
 
     self projectIsLoaded ifTrue:[
-        asAutoloaded ifFalse:[
-            "/ to be considered !!
+	asAutoloaded ifFalse:[
+	    "/ to be considered !!
 "/            self isFullyLoaded ifFalse:[
 "/                self hasAllExtensionsLoaded ifFalse:[
 "/                    self loadExtensions.
 "/                ].
 "/                self loadAllAutoloadedClasses
 "/            ].
-        ].
-        ^ false
+	].
+	^ false
     ].
 
     "/ the following prevents us from crshing if a project definition's prerequisites
@@ -5581,81 +5581,81 @@
 
     thisContext isRecursive ifTrue:[self breakPoint:#cg. ^ false].    "/ avoid endless loops
     (PackagesBeingLoaded includes:self package) ifTrue:[
-        "/ seems to be a recursive call
-        ^ false
+	"/ seems to be a recursive call
+	^ false
     ].
 
     PackagesBeingLoaded add:self package.
     PackageLoadInProgressQuery
-        answerNotifyLoading:self package
-        do:[
-
-            [
-                newStuffHasBeenLoaded := false.
-
-                Smalltalk silentLoading ifFalse:[
-                    "/ thisContext fullPrintAll.
-                    Logger info:('loading %1%2...'
-                                        bindWith:(asAutoloaded ifTrue:['as autoloaded '] ifFalse:[''])
-                                        with:self name).
-                ].
-
-                self rememberOverwrittenExtensionMethods.
-
-                self activityNotification:'Executing pre-load action'.
-                self executeHooks: #preLoad.
-                self preLoadAction.
-
-                meOrMySecondIncarnation := self.
-
-                Class withoutUpdatingChangesDo:[
-                    self activityNotification:'Loading prerequisities'.
-                    self loadMandatoryPreRequisitesAsAutoloaded:asAutoloaded.
-
-                    self checkPrerequisitesForLoading.
-
-                    asAutoloaded ifFalse:[
-                        "ignore binary class library load failure - try is the hard way (loading classes)"
-                        PackageLoadError ignoreIn:[
-                            self loadClassLibrary.
-                            "/ could have overloaded my first incarnation
-                            meOrMySecondIncarnation := (Smalltalk at:(self name)) ? self.
-                            meOrMySecondIncarnation ~~ self ifTrue:[
-                                meOrMySecondIncarnation fetchSlotsFrom:self.
-                            ].
-                        ].
-                    ].
-
-                    self hasAllExtensionsLoaded ifFalse:[
-                        self activityNotification:'Loading extensions'.
-                        "/ evaluating or here - want extensions to be loaded
-                        newStuffHasBeenLoaded := newStuffHasBeenLoaded | meOrMySecondIncarnation loadExtensions.
-                    ].
-                    (self hasAllClassesLoaded:asAutoloaded not) ifFalse:[
-                        self activityNotification:'Loading classes'.
-                        "/ evaluating or here - want autoloaded classes to be loaded
-                        newStuffHasBeenLoaded := newStuffHasBeenLoaded | (meOrMySecondIncarnation loadAllClassesAsAutoloaded:asAutoloaded).
-                    ].
-                    "/ no, don't load subProjects here - will lead to a recursion, which leads
-                    "/ to some classes being loaded from source (soap)
-                    "/     self activityNotification:'Loading sub projects'.
-                    "/     meOrMySecondIncarnation loadSubProjectsAsAutoloaded:asAutoloaded.
-                ].
-                self activityNotification:('Executing post-load action for %1' bindWith:self package).
-
-                "/ mhmh - already done for dll-loaded packages
-                "/ meOrMySecondIncarnation initializeAllClasses.
-
-                meOrMySecondIncarnation projectIsLoaded:true.
-                meOrMySecondIncarnation ~~ self ifTrue:[
-                    self projectIsLoaded:true.
-                ].
-            ] ensure:[
-                PackagesBeingLoaded remove:self package ifAbsent:[].
-            ].
-            "/ load the other prerequisites
-            self loadPreRequisitesAsAutoloaded:asAutoloaded.
-        ].
+	answerNotifyLoading:self package
+	do:[
+
+	    [
+		newStuffHasBeenLoaded := false.
+
+		Smalltalk silentLoading ifFalse:[
+		    "/ thisContext fullPrintAll.
+		    Logger info:('loading %1%2...'
+					bindWith:(asAutoloaded ifTrue:['as autoloaded '] ifFalse:[''])
+					with:self name).
+		].
+
+		self rememberOverwrittenExtensionMethods.
+
+		self activityNotification:'Executing pre-load action'.
+		self executeHooks: #preLoad.
+		self preLoadAction.
+
+		meOrMySecondIncarnation := self.
+
+		Class withoutUpdatingChangesDo:[
+		    self activityNotification:'Loading prerequisities'.
+		    self loadMandatoryPreRequisitesAsAutoloaded:asAutoloaded.
+
+		    self checkPrerequisitesForLoading.
+
+		    asAutoloaded ifFalse:[
+			"ignore binary class library load failure - try is the hard way (loading classes)"
+			PackageLoadError ignoreIn:[
+			    self loadClassLibrary.
+			    "/ could have overloaded my first incarnation
+			    meOrMySecondIncarnation := (Smalltalk at:(self name)) ? self.
+			    meOrMySecondIncarnation ~~ self ifTrue:[
+				meOrMySecondIncarnation fetchSlotsFrom:self.
+			    ].
+			].
+		    ].
+
+		    self hasAllExtensionsLoaded ifFalse:[
+			self activityNotification:'Loading extensions'.
+			"/ evaluating or here - want extensions to be loaded
+			newStuffHasBeenLoaded := newStuffHasBeenLoaded | meOrMySecondIncarnation loadExtensions.
+		    ].
+		    (self hasAllClassesLoaded:asAutoloaded not) ifFalse:[
+			self activityNotification:'Loading classes'.
+			"/ evaluating or here - want autoloaded classes to be loaded
+			newStuffHasBeenLoaded := newStuffHasBeenLoaded | (meOrMySecondIncarnation loadAllClassesAsAutoloaded:asAutoloaded).
+		    ].
+		    "/ no, don't load subProjects here - will lead to a recursion, which leads
+		    "/ to some classes being loaded from source (soap)
+		    "/     self activityNotification:'Loading sub projects'.
+		    "/     meOrMySecondIncarnation loadSubProjectsAsAutoloaded:asAutoloaded.
+		].
+		self activityNotification:('Executing post-load action for %1' bindWith:self package).
+
+		"/ mhmh - already done for dll-loaded packages
+		"/ meOrMySecondIncarnation initializeAllClasses.
+
+		meOrMySecondIncarnation projectIsLoaded:true.
+		meOrMySecondIncarnation ~~ self ifTrue:[
+		    self projectIsLoaded:true.
+		].
+	    ] ensure:[
+		PackagesBeingLoaded remove:self package ifAbsent:[].
+	    ].
+	    "/ load the other prerequisites
+	    self loadPreRequisitesAsAutoloaded:asAutoloaded.
+	].
     self activityNotification:('Done (%1).' bindWith:self package).
     ^ newStuffHasBeenLoaded
 
@@ -5674,8 +5674,8 @@
     thisContext isRecursive ifTrue:[^ false].
 
     Smalltalk silentLoading ifFalse:[
-        "/ thisContext fullPrintAll.
-        Logger info:'unloading %1' with:self name.
+	"/ thisContext fullPrintAll.
+	Logger info:'unloading %1' with:self name.
     ].
 
     self activityNotification:'Executing pre-unload action'.
@@ -5686,12 +5686,12 @@
     self restoreOverwrittenExtensionMethods.
 
     Class withoutUpdatingChangesDo:[
-        self activityNotification:'Unloading subprojects'.
-        self unloadSubProjects.
-
-        self activityNotification:'Unloading classes'.
-        self unloadClassLibrary.
-        self unloadAllClasses.
+	self activityNotification:'Unloading subprojects'.
+	self unloadSubProjects.
+
+	self activityNotification:'Unloading classes'.
+	self unloadClassLibrary.
+	self unloadAllClasses.
     ].
     self projectIsLoaded:false.
     ^ true
@@ -5710,31 +5710,31 @@
     |abbrevs|
 
     AccessLock critical:[
-        |mustRead file myPackageDirectory|
-
-        AbbrevDictionary isNil ifTrue:[
-            AbbrevDictionary := WeakIdentityDictionary new.
-        ].
-
-        mustRead := false.
-        abbrevs := AbbrevDictionary at:self ifAbsent:[ mustRead := true. Dictionary new ].
-
-        mustRead ifTrue:[
-            myPackageDirectory := self packageDirectory.
-            myPackageDirectory isNil ifTrue:[
-            ] ifFalse:[
-                file := myPackageDirectory / 'abbrev.stc'.
-                file exists ifTrue: [
-                    file readingFileDo:[:stream |
-                        Smalltalk
-                            withAbbreviationsFromStream:stream
-                            do:[:nm :fn :pkg :cat :sz|
-                                abbrevs at: nm put: (AbbrevEntry new className:nm fileName:fn category:cat numClassInstVars:sz)
-                            ]
-                    ]
-                ].
-            ].
-        ].
+	|mustRead file myPackageDirectory|
+
+	AbbrevDictionary isNil ifTrue:[
+	    AbbrevDictionary := WeakIdentityDictionary new.
+	].
+
+	mustRead := false.
+	abbrevs := AbbrevDictionary at:self ifAbsent:[ mustRead := true. Dictionary new ].
+
+	mustRead ifTrue:[
+	    myPackageDirectory := self packageDirectory.
+	    myPackageDirectory isNil ifTrue:[
+	    ] ifFalse:[
+		file := myPackageDirectory / 'abbrev.stc'.
+		file exists ifTrue: [
+		    file readingFileDo:[:stream |
+			Smalltalk
+			    withAbbreviationsFromStream:stream
+			    do:[:nm :fn :pkg :cat :sz|
+				abbrevs at: nm put: (AbbrevEntry new className:nm fileName:fn category:cat numClassInstVars:sz)
+			    ]
+		    ]
+		].
+	    ].
+	].
     ].
 
     ^abbrevs
@@ -5759,21 +5759,21 @@
      #'module:package/subpackage/tests'
     "
     ((self package endsWith: '/tests') or:[(self package endsWith: '/test')]) ifFalse:[
-        (TestCase notNil and:[aClass inheritsFrom: TestCase]) ifTrue:[^#(autoload)].
-        (TestResource notNil and:[aClass inheritsFrom: TestResource]) ifTrue:[^#(autoload)].
+	(TestCase notNil and:[aClass inheritsFrom: TestCase]) ifTrue:[^#(autoload)].
+	(TestResource notNil and:[aClass inheritsFrom: TestResource]) ifTrue:[^#(autoload)].
     ].
 
     "No additional attributes"
     ^#()
 
     "
-        stx_libbasic additionalClassAttributesFor: Object
-        stx_libtool additionalClassAttributesFor: Tools::NavigationHistoryTests
-        stx_goodies_sunit additionalClassAttributesFor: TestCase
-        stx_goodies_petitparser_tests additionalClassAttributesFor: PPAbstractParseTest
-
-
-        stx_libtool classNamesAndAttributes_code_ignoreOldEntries:true ignoreOldDefinition: true
+	stx_libbasic additionalClassAttributesFor: Object
+	stx_libtool additionalClassAttributesFor: Tools::NavigationHistoryTests
+	stx_goodies_sunit additionalClassAttributesFor: TestCase
+	stx_goodies_petitparser_tests additionalClassAttributesFor: PPAbstractParseTest
+
+
+	stx_libtool classNamesAndAttributes_code_ignoreOldEntries:true ignoreOldDefinition: true
 
     "
 
@@ -5790,33 +5790,33 @@
     nonExistentClasses := Set new.
 
     check :=
-            [:eachClassName |
-                |cls fn wasLoaded failedToLoad numClassInstvars|
-
-                cls := Smalltalk classNamed:eachClassName.
-                cls isNil ifTrue:[
-                    Transcript showCR:eachClassName.
-                    nonExistentClasses add:eachClassName.
-                ].
-            ].
+	    [:eachClassName |
+		|cls fn wasLoaded failedToLoad numClassInstvars|
+
+		cls := Smalltalk classNamed:eachClassName.
+		cls isNil ifTrue:[
+		    Transcript showCR:eachClassName.
+		    nonExistentClasses add:eachClassName.
+		].
+	    ].
 
     self allClassNames do:check.
     self namesAndAttributesIn:(self additionalClassNamesAndAttributes) do:[:nm :attr |
-        (attr isEmptyOrNil or:[(attr includes:#autoload) not]) ifTrue:[
-            check value:nm
-        ].
+	(attr isEmptyOrNil or:[(attr includes:#autoload) not]) ifTrue:[
+	    check value:nm
+	].
     ].
 
     nonExistentClasses notEmpty ifTrue:[
-        Transcript showCR:('"%1" and possibly more classes are missing.\Cannot generate a correct "abbrev.stc" file.' bindWith:nonExistentClasses).
-        UserPreferences current suppressProjectDefinitionWarnings ifFalse:[
-            (Dialog confirm:(Dialog classResources
-                                stringWithCRs:'"%1" and possibly more classes are missing.\Cannot generate a correct "abbrev.stc" file.\\Continue anyway?'
-                                with:nonExistentClasses anElement allBold)) ifFalse:[
-                AbortOperationRequest raise.
-            ].
-        ].
-        ^ false.
+	Transcript showCR:('"%1" and possibly more classes are missing.\Cannot generate a correct "abbrev.stc" file.' bindWith:nonExistentClasses).
+	UserPreferences current suppressProjectDefinitionWarnings ifFalse:[
+	    (Dialog confirm:(Dialog classResources
+				stringWithCRs:'"%1" and possibly more classes are missing.\Cannot generate a correct "abbrev.stc" file.\\Continue anyway?'
+				with:nonExistentClasses anElement allBold)) ifFalse:[
+		AbortOperationRequest raise.
+	    ].
+	].
+	^ false.
     ].
 
     ^ true
@@ -5829,16 +5829,16 @@
      This decompresses class-name entries into a one-element array for easier processing"
 
     ^ self classNamesAndAttributes
-        collect:[:entry |
-            entry isArray ifTrue:[
-                entry first isSymbol ifTrue:[
-                    entry
-                ] ifFalse:[
-                    (Array with:entry first asSymbol) , (entry copyFrom:2)
-                ].
-            ] ifFalse:[
-                Array with:entry asSymbol.
-            ]].
+	collect:[:entry |
+	    entry isArray ifTrue:[
+		entry first isSymbol ifTrue:[
+		    entry
+		] ifFalse:[
+		    (Array with:entry first asSymbol) , (entry copyFrom:2)
+		].
+	    ] ifFalse:[
+		Array with:entry asSymbol.
+	    ]].
 
     "Created: / 19-02-2007 / 16:11:53 / cg"
 !
@@ -5861,44 +5861,44 @@
     entriesByName := Dictionary new.
 
     newSpec :=
-        aSpecArray
-            collect:[:entry |
-                |nm newEntry|
-
-                (entry isArray and:[entry size == 1]) ifTrue:[
-                    nm := newEntry := entry first.
-                    entriesByName at:nm put:nm.
-                ] ifFalse:[
-                    newEntry := entry.
-                    (entry isArray and:[entry size > 1]) ifTrue:[
-                        nm := entry first.
-                        entriesByName at:nm put:entry.
-                    ] ifFalse:[
-                        nm := entry.
-                        entriesByName at:nm put:entry.
-                    ].
-                ].
-                newEntry
-            ].
+	aSpecArray
+	    collect:[:entry |
+		|nm newEntry|
+
+		(entry isArray and:[entry size == 1]) ifTrue:[
+		    nm := newEntry := entry first.
+		    entriesByName at:nm put:nm.
+		] ifFalse:[
+		    newEntry := entry.
+		    (entry isArray and:[entry size > 1]) ifTrue:[
+			nm := entry first.
+			entriesByName at:nm put:entry.
+		    ] ifFalse:[
+			nm := entry.
+			entriesByName at:nm put:entry.
+		    ].
+		].
+		newEntry
+	    ].
 
     "/ extract loaded and unloaded classes.
     loadedClasses := OrderedCollection new.
     itemsForUnloadedClasses := OrderedCollection new.
 
     newSpec do:[:entry |
-        |clsName clsOrNil|
-
-        (entry isArray and:[entry includes:#autoload]) ifTrue:[
-            itemsForUnloadedClasses add:entry.
-        ] ifFalse:[    
-            clsName := entry isArray ifTrue:[ entry first ] ifFalse:[ entry ].
-            clsOrNil := Smalltalk classNamed:clsName.
-            (clsOrNil notNil and:[clsOrNil isLoaded]) ifTrue:[
-                loadedClasses add:clsOrNil.
-            ] ifFalse:[
-                itemsForUnloadedClasses add:entry.
-            ]
-        ]
+	|clsName clsOrNil|
+
+	(entry isArray and:[entry includes:#autoload]) ifTrue:[
+	    itemsForUnloadedClasses add:entry.
+	] ifFalse:[
+	    clsName := entry isArray ifTrue:[ entry first ] ifFalse:[ entry ].
+	    clsOrNil := Smalltalk classNamed:clsName.
+	    (clsOrNil notNil and:[clsOrNil isLoaded]) ifTrue:[
+		loadedClasses add:clsOrNil.
+	    ] ifFalse:[
+		itemsForUnloadedClasses add:entry.
+	    ]
+	]
     ].
     "/ and sort by load order
     loadedClassNames := (Class classesSortedByLoadOrder:loadedClasses) collect:[:cls | cls name].
@@ -5914,31 +5914,31 @@
 
 compile:someCode categorized:category using:compilerOrNil
     ^ Class packageQuerySignal
-        answer:self package
-        do:[
-            (compilerOrNil ? self theMetaclass compilerClass)
-                compile:someCode
-                forClass:self theMetaclass
-                inCategory:category
-        ]
+	answer:self package
+	do:[
+	    (compilerOrNil ? self theMetaclass compilerClass)
+		compile:someCode
+		forClass:self theMetaclass
+		inCategory:category
+	]
 
     "Created: / 23-08-2006 / 14:36:53 / cg"
 !
 
 compiled_classes
     ^ self compiled_classNames
-        collect:
-            [:eachName|
-                |cls|
-
-                cls := (Smalltalk at:eachName asSymbol).
-                (cls isNil or:[cls isBehavior not]) ifTrue:[
-                    Transcript showCR:('ProjectDefinition: missing/invalid class: ', eachName).
-                    cls := nil.
-                ].
-                cls.
-            ]
-        thenSelect:[:cls | cls notNil]
+	collect:
+	    [:eachName|
+		|cls|
+
+		cls := (Smalltalk at:eachName asSymbol).
+		(cls isNil or:[cls isBehavior not]) ifTrue:[
+		    Transcript showCR:('ProjectDefinition: missing/invalid class: ', eachName).
+		    cls := nil.
+		].
+		cls.
+	    ]
+	thenSelect:[:cls | cls notNil]
 
     "Created: / 09-08-2006 / 16:28:15 / fm"
     "Modified: / 09-08-2006 / 18:02:28 / fm"
@@ -5954,7 +5954,7 @@
 
 compiled_classesForPlatform:arch
     ^ (self compiled_classNamesForPlatform:arch)
-        collect:[:eachName | (Smalltalk classNamed:eachName)]
+	collect:[:eachName | (Smalltalk classNamed:eachName)]
 
     "
      stx_libbasic compiled_classesForArchitecture:#win32
@@ -5969,23 +5969,23 @@
 
 compiled_classes_common
     ^ self
-        compiled_classNames_common
-            collect:[:eachName |
-                |cls|
-
-                cls := Smalltalk classNamed:eachName.
-                cls isNil ifTrue:[
-                    Transcript showCR:('Warning: Missing/invalid class: %1 - the class is skipped in the list of compiled classes.').
-                    UserPreferences current suppressProjectDefinitionWarnings ifFalse:[
-                        self warn:('Missing/invalid class: %1\\%2'
-                                    bindWith:eachName
-                                    with:('Warning: The class is skipped in the list of compiled classes.' allBold)) withCRs.
-                    ].
-                    cls := nil.
-                ].
-                cls
-            ]
-            thenSelect:[:cls| cls notNil "isBehavior"]
+	compiled_classNames_common
+	    collect:[:eachName |
+		|cls|
+
+		cls := Smalltalk classNamed:eachName.
+		cls isNil ifTrue:[
+		    Transcript showCR:('Warning: Missing/invalid class: %1 - the class is skipped in the list of compiled classes.').
+		    UserPreferences current suppressProjectDefinitionWarnings ifFalse:[
+			self warn:('Missing/invalid class: %1\\%2'
+				    bindWith:eachName
+				    with:('Warning: The class is skipped in the list of compiled classes.' allBold)) withCRs.
+		    ].
+		    cls := nil.
+		].
+		cls
+	    ]
+	    thenSelect:[:cls| cls notNil "isBehavior"]
 
     "Created: / 09-08-2006 / 16:28:15 / fm"
     "Modified: / 09-08-2006 / 18:02:28 / fm"
@@ -5997,8 +5997,8 @@
 
     rev := self revision.
     rev isNil ifTrue:[
-        "not yet pubplished"
-        ^ #( '0' '1' )
+	"not yet pubplished"
+	^ #( '0' '1' )
     ].
     ^ rev asCollectionOfSubstringsSeparatedBy:$. .
 
@@ -6022,8 +6022,8 @@
      Add a programming language attribute for non-smalltalk classes.
      Used by multi-lang enabled loading mechanism"
     attrs := aClass programmingLanguage isSmalltalk
-                ifTrue:[#()]
-                ifFalse:[Array with: (Array with: #lang with: aClass programmingLanguage name asSymbol)].
+		ifTrue:[#()]
+		ifFalse:[Array with: (Array with: #lang with: aClass programmingLanguage name asSymbol)].
 
 
     "JV @ 2009-10-26
@@ -6087,16 +6087,16 @@
     aCollection isNil ifTrue:[^ self].
 
     aCollection do:[:entry |
-        |className attributes|
-
-        entry isArray ifFalse:[
-            className := entry.
-            attributes := #().
-        ] ifTrue:[
-            className := entry first.
-            attributes := entry copyFrom:2.
-        ].
-        aBlock value: className value: attributes
+	|className attributes|
+
+	entry isArray ifFalse:[
+	    className := entry.
+	    attributes := #().
+	] ifTrue:[
+	    className := entry first.
+	    attributes := entry copyFrom:2.
+	].
+	aBlock value: className value: attributes
      ].
 
     "Created: / 22-08-2006 / 18:20:09 / cg"
@@ -6121,7 +6121,7 @@
     "answer all public and private classes belonging to aProjectID"
 
     ^ Smalltalk allClasses
-        select:[:cls | cls package = aProjectID].
+	select:[:cls | cls package = aProjectID].
 
 "
     self searchForClassesWithProject: #'exept:ctypes'
@@ -6153,21 +6153,21 @@
 
     methods := Smalltalk allExtensionsForPackage:aProjectID.
     methods
-        sort:[:m1 :m2 |
-            |c1 c2|
-
-            c1 := m1 mclass.
-            c2 := m2 mclass.
-            c1 == c2 ifTrue:[
-                m1 selector < m2 selector
-            ] ifFalse:[
-                (c2 isMeta and:[c1 isMeta not]) ifTrue:[
-                    true
-                ] ifFalse:[
-                    (c1 isMeta and:[c2 isMeta not]) ifTrue:[
-                        false
-                    ] ifFalse:[
-                        c1 name < c2 name
+	sort:[:m1 :m2 |
+	    |c1 c2|
+
+	    c1 := m1 mclass.
+	    c2 := m2 mclass.
+	    c1 == c2 ifTrue:[
+		m1 selector < m2 selector
+	    ] ifFalse:[
+		(c2 isMeta and:[c1 isMeta not]) ifTrue:[
+		    true
+		] ifFalse:[
+		    (c1 isMeta and:[c2 isMeta not]) ifTrue:[
+			false
+		    ] ifFalse:[
+			c1 name < c2 name
 "/                        (c2 isSubclassOf:c1) ifTrue:[
 "/                            true
 "/                        ] ifFalse:[
@@ -6178,10 +6178,10 @@
 "/                                true
 "/                            ].
 "/                        ].
-                    ].
-                ].
-            ].
-        ].
+		    ].
+		].
+	    ].
+	].
     ^ methods
 
     "
@@ -6201,19 +6201,19 @@
     requiredPackages := Set new.
 
     addPackage :=
-        [:package |
-            (package ~= myPackageID) ifTrue:[
-                true "(package startsWith:'stx:') not" ifTrue:[
-                    package ~= PackageId noProjectID ifTrue:[
-                        requiredPackages add:package.
-                    ]
-                ]
-            ]
-        ].
+	[:package |
+	    (package ~= myPackageID) ifTrue:[
+		true "(package startsWith:'stx:') not" ifTrue:[
+		    package ~= PackageId noProjectID ifTrue:[
+			requiredPackages add:package.
+		    ]
+		]
+	    ]
+	].
 
     "/ need them also...
     self mandatoryPreRequisites do:[:eachPreRequisitePackage |
-        addPackage value:eachPreRequisitePackage
+	addPackage value:eachPreRequisitePackage
     ].
 
     "/ cg: also need include lines for all referenced packages,
@@ -6226,43 +6226,43 @@
     "/ actually, the question is, if then the package should not be listed in the
     "/ mandatoryPrereqs right away. Discuss this with sv.
     self referencedPreRequisites do:[:eachPreRequisitePackage |
-        addPackage value:eachPreRequisitePackage
+	addPackage value:eachPreRequisitePackage
     ].
 
     self compiled_classesDo:[:cls |
-        cls allSuperclassesDo:[:eachSuperClass |
-            addPackage value:(eachSuperClass package)
-        ].
-
-        cls allPrivateClassesDo:[:eachPrivateClass |
-            eachPrivateClass allSuperclassesDo:[:eachSuperClass |
-                eachSuperClass isPrivate ifFalse:[
-                    addPackage value:(eachSuperClass package)
-                ].
-            ]
-        ].
-
-        cls sharedPoolNames do:[:eachPoolName |
-            |eachPoolClass|
-
-            eachPoolClass := Smalltalk classNamed:eachPoolName.
-            eachPoolClass isNil ifTrue:[
-                Transcript showCR:('Warning: missing pool: %1 (required by %2)' bindWith:eachPoolName with:cls name)
-            ] ifFalse:[
-                eachPoolClass withAllSuperclassesDo:[:eachPoolSuperClass |
-                    addPackage value:(eachPoolSuperClass package)
-                ]
-            ]
-        ].
+	cls allSuperclassesDo:[:eachSuperClass |
+	    addPackage value:(eachSuperClass package)
+	].
+
+	cls allPrivateClassesDo:[:eachPrivateClass |
+	    eachPrivateClass allSuperclassesDo:[:eachSuperClass |
+		eachSuperClass isPrivate ifFalse:[
+		    addPackage value:(eachSuperClass package)
+		].
+	    ]
+	].
+
+	cls sharedPoolNames do:[:eachPoolName |
+	    |eachPoolClass|
+
+	    eachPoolClass := Smalltalk classNamed:eachPoolName.
+	    eachPoolClass isNil ifTrue:[
+		Transcript showCR:('Warning: missing pool: %1 (required by %2)' bindWith:eachPoolName with:cls name)
+	    ] ifFalse:[
+		eachPoolClass withAllSuperclassesDo:[:eachPoolSuperClass |
+		    addPackage value:(eachPoolSuperClass package)
+		]
+	    ]
+	].
     ].
 
     self extensionMethodNames pairWiseDo:[:className :selector |
-        |cls|
-        ((cls := Smalltalk classNamed:className) notNil and:[cls isLoaded]) ifTrue:[
-            cls withAllSuperclassesDo:[:eachSuperClass |
-                addPackage value:(eachSuperClass package)
-            ]
-        ]
+	|cls|
+	((cls := Smalltalk classNamed:className) notNil and:[cls isLoaded]) ifTrue:[
+	    cls withAllSuperclassesDo:[:eachSuperClass |
+		addPackage value:(eachSuperClass package)
+	    ]
+	]
     ].
     ^ requiredPackages
 
@@ -6286,12 +6286,12 @@
     myParentPackage isNil ifTrue:[^ #() ].
 
     ^ Smalltalk allPackageIDs
-        select:[:projectID |
-            |thisPackage|
-            thisPackage := projectID asPackageId.
-            (thisPackage parentPackage = myParentPackage)
-            and:[ thisPackage ~= myPackage ].
-        ]
+	select:[:projectID |
+	    |thisPackage|
+	    thisPackage := projectID asPackageId.
+	    (thisPackage parentPackage = myParentPackage)
+	    and:[ thisPackage ~= myPackage ].
+	]
 
     "
      self searchForSiblingProjects
@@ -6310,9 +6310,9 @@
 
     myPackage := self package.
     ^ Smalltalk allPackageIDs
-        select:[:projectID |
-            projectID ~= PackageId noProjectID
-            and:[ (projectID asPackageId parentPackage) = myPackage ]].
+	select:[:projectID |
+	    projectID ~= PackageId noProjectID
+	    and:[ (projectID asPackageId parentPackage) = myPackage ]].
 
     "
      self searchForSubProjects
@@ -6327,29 +6327,29 @@
 
 setupForType:typeOrNil
     typeOrNil = GUIApplicationType ifTrue:[
-        self compile:
+	self compile:
 'isGUIApplication
     "return true, if this is a GUI application.
      (these need more libraries and use a different startup procedure)"
 
     ^ true
 '
-             categorized:'description'.
-        self setSuperclass: ApplicationDefinition.
-        ^ self
+	     categorized:'description'.
+	self setSuperclass: ApplicationDefinition.
+	^ self
     ].
 
     typeOrNil = NonGUIApplicationType ifTrue:[
-        self compile:
+	self compile:
 'isGUIApplication
     "return true, if this is a GUI application.
      (these need more libraries and use a different startup procedure)"
 
     ^ false
 '
-             categorized:'description'.
-        self setSuperclass: ApplicationDefinition.
-        ^ self
+	     categorized:'description'.
+	self setSuperclass: ApplicationDefinition.
+	^ self
     ].
 
     self theMetaclass removeSelector: #isGUIApplication.
@@ -6361,9 +6361,9 @@
 
 shouldExcludeTest: test
     ^ self excludedFromTestSuite contains:[:spec|
-            (spec isSymbol and:[test class name == spec])
-            or:[spec isArray and:[test class name == spec first and:[test selector == spec second]]]
-        ].
+	    (spec isSymbol and:[test class name == spec])
+	    or:[spec isArray and:[test class name == spec first and:[test selector == spec second]]]
+	].
 
     "Created: / 03-06-2011 / 17:01:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -6413,36 +6413,36 @@
     oldPackage := extensionOverwriteInfo at:(mclass name,'>>',selector) ifAbsent:nil.
     oldPackage isNil ifTrue:[^ nil].
     ^ oldPackage asPackageId projectDefinitionClass
-        savedOverwrittenMethodForClass:mclass selector:selector.
+	savedOverwrittenMethodForClass:mclass selector:selector.
 !
 
 rememberOverwrittenExtensionMethods
     "before loading, tell other packages to keep a safe reference to any method
      which gets overloaded by me, and also remember here, whome I have overloaded.
      This allows for two things:
-        a) correct fileout of the other base-package (for example, when checking in any of its class)
-        b) correct unloading of myself"
+	a) correct fileout of the other base-package (for example, when checking in any of its class)
+	b) correct unloading of myself"
 
     self extensionMethodNames pairWiseDo:[:className :selector |
-        |class oldMethod oldPackage defClass|
-
-        class := Smalltalk classNamed:className.
-        class notNil ifTrue:[
-            oldMethod := class compiledMethodAt:selector.
-        ].
-        oldMethod notNil ifTrue:[
-            oldPackage := oldMethod package.
-            oldPackage ~= PackageId noProjectID ifTrue:[
-                defClass := oldPackage asPackageId projectDefinitionClass.
-                defClass notNil ifTrue:[
-                    defClass rememberOverwrittenMethod:oldMethod inClass:class.
-                    extensionOverwriteInfo isNil ifTrue:[
-                        extensionOverwriteInfo := Dictionary new.
-                    ].
-                    extensionOverwriteInfo at:(className,'>>',selector) put:oldPackage.
-                ]
-            ].
-        ].
+	|class oldMethod oldPackage defClass|
+
+	class := Smalltalk classNamed:className.
+	class notNil ifTrue:[
+	    oldMethod := class compiledMethodAt:selector.
+	].
+	oldMethod notNil ifTrue:[
+	    oldPackage := oldMethod package.
+	    oldPackage ~= PackageId noProjectID ifTrue:[
+		defClass := oldPackage asPackageId projectDefinitionClass.
+		defClass notNil ifTrue:[
+		    defClass rememberOverwrittenMethod:oldMethod inClass:class.
+		    extensionOverwriteInfo isNil ifTrue:[
+			extensionOverwriteInfo := Dictionary new.
+		    ].
+		    extensionOverwriteInfo at:(className,'>>',selector) put:oldPackage.
+		]
+	    ].
+	].
     ].
 !
 
@@ -6457,24 +6457,24 @@
     selector := oldMethod selector.
 
     thisIsOneOfMyMethods := (self classNames includes:aClass theNonMetaclass name)
-                            or:[ aClass isPrivate and:[ self classNames includes: aClass topOwningClass theNonMetaclass name ]].
+			    or:[ aClass isPrivate and:[ self classNames includes: aClass topOwningClass theNonMetaclass name ]].
     thisIsOneOfMyMethods ifFalse:[
-        self extensionMethodNames pairWiseDo:[:extClassName :extSelector |
-            extClassName = aClass name ifTrue:[
-                selector = extSelector ifTrue:[
-                    thisIsOneOfMyMethods := true
-                ].
-            ].
-        ]
+	self extensionMethodNames pairWiseDo:[:extClassName :extSelector |
+	    extClassName = aClass name ifTrue:[
+		selector = extSelector ifTrue:[
+		    thisIsOneOfMyMethods := true
+		].
+	    ].
+	]
     ].
     thisIsOneOfMyMethods ifFalse:[
-        "/ self error:'oops - this is not one of my methods' mayProceed:true.
-        Transcript showCR:self name,' [warning]:not one of my methods in rememberOverwritten'.
-        ^ self
+	"/ self error:'oops - this is not one of my methods' mayProceed:true.
+	Transcript showCR:self name,' [warning]:not one of my methods in rememberOverwritten'.
+	^ self
     ].
 
     safeForOverwrittenMethods isNil ifTrue:[
-        safeForOverwrittenMethods := Dictionary new.
+	safeForOverwrittenMethods := Dictionary new.
     ].
     safeForOverwrittenMethods at:(aClass name,'>>',selector) put:oldMethod.
 !
@@ -6485,20 +6485,20 @@
      Unfinished!!"
 
     extensionOverwriteInfo notEmptyOrNil ifTrue:[
-        self extensionMethodNames pairWiseDo:[:className :selector |
-            |class oldMethod oldPackage|
-
-            oldPackage := extensionOverwriteInfo at:(className,'>>',selector).
-            oldPackage notNil ifTrue:[
-                class := Smalltalk classNamed:className.
-                class notNil ifTrue:[
-                    oldMethod := oldPackage savedOverwrittenMethodForClass:class selector:selector.
-                    oldMethod notNil ifTrue:[
-                        self breakPoint:#cg.
-                    ].
-                ]
-            ].
-        ].
+	self extensionMethodNames pairWiseDo:[:className :selector |
+	    |class oldMethod oldPackage|
+
+	    oldPackage := extensionOverwriteInfo at:(className,'>>',selector).
+	    oldPackage notNil ifTrue:[
+		class := Smalltalk classNamed:className.
+		class notNil ifTrue:[
+		    oldMethod := oldPackage savedOverwrittenMethodForClass:class selector:selector.
+		    oldMethod notNil ifTrue:[
+			self breakPoint:#cg.
+		    ].
+		]
+	    ].
+	].
     ].
 
     "Modified (comment): / 18-05-2017 / 14:49:39 / mawalch"
@@ -6532,23 +6532,23 @@
     classesAlreadyWarned := Set new.
 
     self extensionMethodNames
-        pairWiseDo:[:className :selector |
-            |class errMsg|
-
-            class := Smalltalk classNamed:className.
-            class isNil ifTrue:[
-                (classesAlreadyWarned includes:className) ifFalse:[
-                    (self classNames includes:className) ifTrue:[
-                        errMsg := 'extension for a class in myself: ',className.
-                    ] ifFalse:[
-                        errMsg := 'missing class for extension: ',className.
-                    ].
-                    Logger error:errMsg.
-                    self proceedableError:errMsg.
-                    classesAlreadyWarned add:className.
-                ].
-            ].
-        ]
+	pairWiseDo:[:className :selector |
+	    |class errMsg|
+
+	    class := Smalltalk classNamed:className.
+	    class isNil ifTrue:[
+		(classesAlreadyWarned includes:className) ifFalse:[
+		    (self classNames includes:className) ifTrue:[
+			errMsg := 'extension for a class in myself: ',className.
+		    ] ifFalse:[
+			errMsg := 'missing class for extension: ',className.
+		    ].
+		    Logger error:errMsg.
+		    self proceedableError:errMsg.
+		    classesAlreadyWarned add:className.
+		].
+	    ].
+	]
 
     "/ todo: more needed here...
 
@@ -6568,16 +6568,16 @@
     cls := self.
 
     [ cls notNil ] whileTrue:[
-        cls class selectorsAndMethodsDo:[:selector :method|
-            (method annotationAt: hookSymbol) notNil ifTrue:[
-                method numArgs == 0 ifTrue:[
-                    self perform: selector
-                ] ifFalse:[
-                    self proceedableError:'Hook for %1 may not have arguments'.
-                ]
-            ]
-        ].
-        cls := cls superclass.
+	cls class selectorsAndMethodsDo:[:selector :method|
+	    (method annotationAt: hookSymbol) notNil ifTrue:[
+		method numArgs == 0 ifTrue:[
+		    self perform: selector
+		] ifFalse:[
+		    self proceedableError:'Hook for %1 may not have arguments'.
+		]
+	    ]
+	].
+	cls := cls superclass.
     ].
 
     "Created: / 20-11-2012 / 23:00:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -6624,108 +6624,108 @@
 
     hasClassesToLoad := false.
     self classNamesAndAttributesDo:[:eachClassname :eachAttributes |
-        |eachClassnameSym isAutoload clsLangAttr clsLang cls |
-
-        eachClassnameSym := eachClassname asSymbol.
-        isAutoload := asAutoloaded or:[eachAttributes includes:#autoload].
-        clsLangAttr := eachAttributes detect:[:a| a isArray and: [a size == 2 and:[a first == #lang]]] ifNone:[nil].
-        clsLang := clsLangAttr
-                    ifNil:[SmalltalkLanguage instance]
-                    ifNotNil:[ProgrammingLanguage named: clsLangAttr second ifNone:[nil]].
-        classNamesToLangs at: eachClassname put: clsLang.
-
-        "no need to (re-)load an existing class, but install if should be loaded"
-        cls := Smalltalk loadedClassNamed:eachClassnameSym.
-        ((cls isNil or:[cls isLoaded not and:[isAutoload not]]) and:[clsLang notNil and:[langs includes: clsLang]]) ifTrue:[
-            (eachAttributes isEmpty
-             or:[(eachAttributes size == 1 and:[isAutoload])
-             or:[(eachAttributes includes:platformName)
-             or:[eachAttributes contains:[:a| a isArray]]]]) "/FIXME: Hack."
-                ifTrue:[
-                    hasClassesToLoad := true.
-                    isAutoload ifTrue:[
-                        classNamesToAutoload add:eachClassnameSym.
-                    ] ifFalse:[
-                        classNamesToLoad add:eachClassnameSym.
-                    ].
-                ].
-        ].
+	|eachClassnameSym isAutoload clsLangAttr clsLang cls |
+
+	eachClassnameSym := eachClassname asSymbol.
+	isAutoload := asAutoloaded or:[eachAttributes includes:#autoload].
+	clsLangAttr := eachAttributes detect:[:a| a isArray and: [a size == 2 and:[a first == #lang]]] ifNone:[nil].
+	clsLang := clsLangAttr
+		    ifNil:[SmalltalkLanguage instance]
+		    ifNotNil:[ProgrammingLanguage named: clsLangAttr second ifNone:[nil]].
+	classNamesToLangs at: eachClassname put: clsLang.
+
+	"no need to (re-)load an existing class, but install if should be loaded"
+	cls := Smalltalk loadedClassNamed:eachClassnameSym.
+	((cls isNil or:[cls isLoaded not and:[isAutoload not]]) and:[clsLang notNil and:[langs includes: clsLang]]) ifTrue:[
+	    (eachAttributes isEmpty
+	     or:[(eachAttributes size == 1 and:[isAutoload])
+	     or:[(eachAttributes includes:platformName)
+	     or:[eachAttributes contains:[:a| a isArray]]]]) "/FIXME: Hack."
+		ifTrue:[
+		    hasClassesToLoad := true.
+		    isAutoload ifTrue:[
+			classNamesToAutoload add:eachClassnameSym.
+		    ] ifFalse:[
+			classNamesToLoad add:eachClassnameSym.
+		    ].
+		].
+	].
     ].
 
     hasClassesToLoad ifTrue:[
-        loadedClasses := OrderedCollection new.
-
-        self packageDirectory isNil ifTrue:[
-            classNamesToLoad notEmpty ifTrue:[
-                "required classes are missing.
-                 Autoloaded classes are considered as optional..."
-                self
-                    error:(self name,'[error] cannot install because packageDirectory is unknown for missing classes: ', classNamesToLoad printString)
-                    mayProceed:true.
-                ^ false.
-            ].
-            (self name,'[info] cannot install autoloaded classes because packageDirectory is unknown') infoPrintCR.
-            ^ true.
-        ].
-
-        "we need the abbreviations, since sometimes there is no 1-to-1 mapping
-         of class name to file name"
-
-        Smalltalk recursiveReadAllAbbreviationsFrom:self packageDirectory maxLevels:1.
-
-        "install autoloaded classes first,
-         some others may depend on them"
-
-        classNamesToAutoload withIndexDo:[:eachClassName :index|
-            ActivityNotification
-                raiseRequestWith: ((100 / classNamesToAutoload size ) * index) rounded
-                errorString: 'Autoloading class ', eachClassName.
-
-            self loadClass: eachClassName asAutoloaded: true language: (classNamesToLangs at: eachClassName) .
-        ].
-
-        classesWhichFailedToLoad := OrderedCollection new.
-        classNamesToLoad notEmpty ifTrue:[
-            Verbose ifTrue:[
-                Transcript showCR:('  %1: filing in missing classes (%2) individually...'
-                                    bindWith:self name with:classNamesToLoad size).
-            ]
-        ].
-        classNamesToLoad withIndexDo:[:eachClassName :index|
-            |cls|
-            ActivityNotification
-                raiseRequestWith: ((100 / classNamesToLoad size) * index) rounded
-                errorString: 'Loading class ', eachClassName.
-
-            Error handle:[:ex |
-                "maybe, fileIn failed, because the load order is wrong.
-                 Work around this by installing the class as autoloaded and
-                 loading it"
-
-                classesWhichFailedToLoad add:eachClassName.
-                self loadClass: eachClassName asAutoloaded: true language: (classNamesToLangs at: eachClassName).
-            ] do:[
-                Verbose ifTrue:[
-                    Transcript showCR:('  %1: filing in %2...' bindWith:self name with:eachClassName).
-                ].
-                cls := self loadClass: eachClassName asAutoloaded: false language: (classNamesToLangs at: eachClassName).
-                cls notNil ifTrue:[
-                    loadedClasses add:cls
-                ].
-            ].
-        ].
-
-        classesWhichFailedToLoad do:[:eachClassName |
-            (Smalltalk at:eachClassName) autoload.
-        ].
-
-        loadedClasses do:[:eachLoadedClass |
-            "do not initialize, if initialize method is inherited"
-            (eachLoadedClass theMetaclass includesSelector:#initialize) ifTrue:[
-                eachLoadedClass initialize
-            ].
-        ].
-        ^ true.
+	loadedClasses := OrderedCollection new.
+
+	self packageDirectory isNil ifTrue:[
+	    classNamesToLoad notEmpty ifTrue:[
+		"required classes are missing.
+		 Autoloaded classes are considered as optional..."
+		self
+		    error:(self name,'[error] cannot install because packageDirectory is unknown for missing classes: ', classNamesToLoad printString)
+		    mayProceed:true.
+		^ false.
+	    ].
+	    (self name,'[info] cannot install autoloaded classes because packageDirectory is unknown') infoPrintCR.
+	    ^ true.
+	].
+
+	"we need the abbreviations, since sometimes there is no 1-to-1 mapping
+	 of class name to file name"
+
+	Smalltalk recursiveReadAllAbbreviationsFrom:self packageDirectory maxLevels:1.
+
+	"install autoloaded classes first,
+	 some others may depend on them"
+
+	classNamesToAutoload withIndexDo:[:eachClassName :index|
+	    ActivityNotification
+		raiseRequestWith: ((100 / classNamesToAutoload size ) * index) rounded
+		errorString: 'Autoloading class ', eachClassName.
+
+	    self loadClass: eachClassName asAutoloaded: true language: (classNamesToLangs at: eachClassName) .
+	].
+
+	classesWhichFailedToLoad := OrderedCollection new.
+	classNamesToLoad notEmpty ifTrue:[
+	    Verbose ifTrue:[
+		Transcript showCR:('  %1: filing in missing classes (%2) individually...'
+				    bindWith:self name with:classNamesToLoad size).
+	    ]
+	].
+	classNamesToLoad withIndexDo:[:eachClassName :index|
+	    |cls|
+	    ActivityNotification
+		raiseRequestWith: ((100 / classNamesToLoad size) * index) rounded
+		errorString: 'Loading class ', eachClassName.
+
+	    Error handle:[:ex |
+		"maybe, fileIn failed, because the load order is wrong.
+		 Work around this by installing the class as autoloaded and
+		 loading it"
+
+		classesWhichFailedToLoad add:eachClassName.
+		self loadClass: eachClassName asAutoloaded: true language: (classNamesToLangs at: eachClassName).
+	    ] do:[
+		Verbose ifTrue:[
+		    Transcript showCR:('  %1: filing in %2...' bindWith:self name with:eachClassName).
+		].
+		cls := self loadClass: eachClassName asAutoloaded: false language: (classNamesToLangs at: eachClassName).
+		cls notNil ifTrue:[
+		    loadedClasses add:cls
+		].
+	    ].
+	].
+
+	classesWhichFailedToLoad do:[:eachClassName |
+	    (Smalltalk at:eachClassName) autoload.
+	].
+
+	loadedClasses do:[:eachLoadedClass |
+	    "do not initialize, if initialize method is inherited"
+	    (eachLoadedClass theMetaclass includesSelector:#initialize) ifTrue:[
+		eachLoadedClass initialize
+	    ].
+	].
+	^ true.
     ].
     ^ false.
 
@@ -6740,28 +6740,28 @@
 
     "Handle smalltalk classes specially to provide backward compatibility"
     lang isSmalltalk ifTrue:[
-        entry := self abbrevs at: className ifAbsent:[nil].
-
-        asAutoloaded ifTrue:[
-            category := entry isNil ifTrue:[#autoloaded] ifFalse:[entry category].
-            numClassInstVars := entry isNil ifTrue:[0] ifFalse:[entry numClassInstVars].
-            cls := Smalltalk
-                installAutoloadedClassNamed: className
-                category: category
-                package: self package
-                revision: nil
-                numClassInstVars:numClassInstVars.
-            entry notNil ifTrue:[
-                cls setClassFilename:(entry fileName,'.st').
-            ].
-            ^ cls.
-        ].
-        ^ Smalltalk
-            fileInClass:className
-            package:self package
-            initialize:false
-            lazy:false
-            silent:true
+	entry := self abbrevs at: className ifAbsent:[nil].
+
+	asAutoloaded ifTrue:[
+	    category := entry isNil ifTrue:[#autoloaded] ifFalse:[entry category].
+	    numClassInstVars := entry isNil ifTrue:[0] ifFalse:[entry numClassInstVars].
+	    cls := Smalltalk
+		installAutoloadedClassNamed: className
+		category: category
+		package: self package
+		revision: nil
+		numClassInstVars:numClassInstVars.
+	    entry notNil ifTrue:[
+		cls setClassFilename:(entry fileName,'.st').
+	    ].
+	    ^ cls.
+	].
+	^ Smalltalk
+	    fileInClass:className
+	    package:self package
+	    initialize:false
+	    lazy:false
+	    silent:true
     ].
 
     "For non-smalltalk language do"
@@ -6789,11 +6789,11 @@
     libraryName := self libraryName.
 
     (Smalltalk isClassLibraryLoaded:libraryName) ifTrue:[
-        "already loaded"
-        ^ true
+	"already loaded"
+	^ true
     ].
     Verbose ifTrue:[
-        Transcript showCR:('  %1: loading classLibrary...' bindWith:self name).
+	Transcript showCR:('  %1: loading classLibrary...' bindWith:self name).
     ].
     self activityNotification:'Loading classLibrary'.
 
@@ -6805,12 +6805,12 @@
 
     self supportedOnPlatform ifFalse:[^ false].
     self hasAllExtensionsLoaded ifFalse:[
-        self breakPoint:#cg.
-        Verbose ifTrue:[
-            Transcript showCR:('  %1: filing in extensions...' bindWith:self name).
-        ].
-        Smalltalk loadExtensionsForPackage:self package.
-        ^ true.
+	self breakPoint:#cg.
+	Verbose ifTrue:[
+	    Transcript showCR:('  %1: filing in extensions...' bindWith:self name).
+	].
+	Smalltalk loadExtensionsForPackage:self package.
+	^ true.
     ].
     ^ false.
 
@@ -6827,7 +6827,7 @@
     filename := 'extensions.' , lang sourceFileSuffix.
     file := self packageDirectory / filename.
     file exists ifTrue:[
-        lang fileIn: file.
+	lang fileIn: file.
     ]
 
     "Created: / 17-08-2006 / 00:21:39 / cg"
@@ -6842,15 +6842,15 @@
     |prereq|
 
     self supportedOnPlatform ifFalse:[
-        ^ self
+	^ self
     ].
 
     prereq := self effectiveMandatoryPreRequisites.
     prereq notEmpty ifTrue:[
-        Verbose ifTrue:[
-            Transcript showCR:('  %1 loading mandatory prerequisites...' bindWith:self name).
-        ].
-        self loadPackages:prereq asAutoloaded:asAutoloaded
+	Verbose ifTrue:[
+	    Transcript showCR:('  %1 loading mandatory prerequisites...' bindWith:self name).
+	].
+	self loadPackages:prereq asAutoloaded:asAutoloaded
     ].
 !
 
@@ -6859,14 +6859,14 @@
      If asAutoloaded == true, classes will be only installed as autoloaded."
 
     Class withoutUpdatingChangesDo:[
-        aListOfPackages do:[:eachPackageID |
-            |cls|
-
-            cls := self definitionClassForPackage:eachPackageID.
-            (cls isNil or:[cls isLoaded not or:[cls projectIsLoaded not]]) ifTrue:[
-                Smalltalk loadPackage:eachPackageID asAutoloaded:asAutoloaded.
-            ].
-        ].
+	aListOfPackages do:[:eachPackageID |
+	    |cls|
+
+	    cls := self definitionClassForPackage:eachPackageID.
+	    (cls isNil or:[cls isLoaded not or:[cls projectIsLoaded not]]) ifTrue:[
+		Smalltalk loadPackage:eachPackageID asAutoloaded:asAutoloaded.
+	    ].
+	].
     ].
 
     "Modified: / 09-12-2010 / 12:36:17 / cg"
@@ -6879,10 +6879,10 @@
 
     prereq := self effectivePreRequisites.
     prereq notEmpty ifTrue:[
-        Verbose ifTrue:[
-            Transcript showCR:('  %1 loading prerequisites...' bindWith:self name).
-        ].
-        self loadPackages:prereq asAutoloaded:asAutoloaded
+	Verbose ifTrue:[
+	    Transcript showCR:('  %1 loading prerequisites...' bindWith:self name).
+	].
+	self loadPackages:prereq asAutoloaded:asAutoloaded
     ].
 !
 
@@ -6891,12 +6891,12 @@
 
     self loadSubProjectsAsAutoloaded:false.
     self effectiveSubProjects do:[:p |
-        |subDef|
-
-        subDef := self definitionClassForPackage:p.
-        subDef notNil ifTrue:[
-            subDef loadSubProjects
-        ].
+	|subDef|
+
+	subDef := self definitionClassForPackage:p.
+	subDef notNil ifTrue:[
+	    subDef loadSubProjects
+	].
     ].
 !
 
@@ -6924,110 +6924,110 @@
 
     hasClassesToLoad := false.
     self classNamesAndAttributesDo:[:eachClassname :eachAttributes |
-        |eachClassnameSym isAutoload cls|
-
-        eachClassnameSym := eachClassname asSymbol.
-        isAutoload := asAutoloaded or:[eachAttributes includes:#autoload].
-
-        "no need to (re-)load an existing class, but install if should be loaded"
-        cls := Smalltalk loadedClassNamed:eachClassnameSym.
-        (cls isNil or:[cls isLoaded not and:[isAutoload not]]) ifTrue:[
-            (eachAttributes isEmpty
-             or:[(eachAttributes size == 1 and:[isAutoload])
-             or:[eachAttributes includes:platformName]]) ifTrue:[
-                hasClassesToLoad := true.
-                isAutoload ifTrue:[
-                    classNamesToAutoload add:eachClassnameSym.
-                ] ifFalse:[
-                    classNamesToLoad add:eachClassnameSym.
-                ].
-            ].
-        ].
+	|eachClassnameSym isAutoload cls|
+
+	eachClassnameSym := eachClassname asSymbol.
+	isAutoload := asAutoloaded or:[eachAttributes includes:#autoload].
+
+	"no need to (re-)load an existing class, but install if should be loaded"
+	cls := Smalltalk loadedClassNamed:eachClassnameSym.
+	(cls isNil or:[cls isLoaded not and:[isAutoload not]]) ifTrue:[
+	    (eachAttributes isEmpty
+	     or:[(eachAttributes size == 1 and:[isAutoload])
+	     or:[eachAttributes includes:platformName]]) ifTrue:[
+		hasClassesToLoad := true.
+		isAutoload ifTrue:[
+		    classNamesToAutoload add:eachClassnameSym.
+		] ifFalse:[
+		    classNamesToLoad add:eachClassnameSym.
+		].
+	    ].
+	].
     ].
 
     hasClassesToLoad ifTrue:[
-        loadedClasses := OrderedCollection new.
-
-        self packageDirectory isNil ifTrue:[
-            self
-                error:(self name,'[error] cannot install because packageDirectory is unknown')
-                mayProceed:true.
-            ^ false.
-        ].
-
-        "we need the abbreviations, since sometimes there is no 1-to-1 mapping
-         of class name to file name"
-
-        Smalltalk recursiveReadAllAbbreviationsFrom:self packageDirectory maxLevels:1.
-
-        "install autoloaded classes first,
-         some others may depend on them"
-
-        classNamesToAutoload withIndexDo:[:eachClassName :index|
-            ActivityNotification
-                raiseRequestWith: ((100 / classNamesToAutoload size ) * index) rounded
-                errorString: 'Autoloading class ', eachClassName.
-
-            Smalltalk
-                installAutoloadedClassNamed:eachClassName
-                category:#autoloaded    "FIXME"
-                package:self package
-                revision:nil
-                numClassInstVars:0.     "FIXME"
-        ].
-
-        classesWhichFailedToLoad := OrderedCollection new.
-        classNamesToLoad notEmpty ifTrue:[
-            Verbose ifTrue:[
-                Transcript showCR:('  %1: filing in missing classes (%2) individually...'
-                                    bindWith:self name with:classNamesToLoad size).
-            ]
-        ].
-        classNamesToLoad withIndexDo:[:eachClassName :index|
-            |cls|
-            ActivityNotification
-                raiseRequestWith: ((100 / classNamesToLoad size) * index) rounded
-                errorString: 'Loading class ', eachClassName.
-
-            Error handle:[:ex |
-                "maybe, fileIn failed, because the load order is wrong.
-                 Work around this by installing the class as autoloaded and
-                 loading it"
-
-                classesWhichFailedToLoad add:eachClassName.
-                Smalltalk
-                    installAutoloadedClassNamed:eachClassName
-                    category:#autoloaded    "FIXME"
-                    package:self package
-                    revision:nil
-                    numClassInstVars:0.     "FIXME"
-            ] do:[
-                Verbose ifTrue:[
-                    Transcript showCR:('  %1: filing in %2...' bindWith:self name with:eachClassName).
-                ].
-                cls := Smalltalk
-                            fileInClass:eachClassName
-                            package:self package
-                            initialize:false
-                            lazy:false
-                            silent:true.
-                cls notNil ifTrue:[
-                    loadedClasses add:cls
-                ].
-            ].
-        ].
-
-        classesWhichFailedToLoad do:[:eachClassName |
-            (Smalltalk at:eachClassName) autoload.
-        ].
-
-        loadedClasses do:[:eachLoadedClass |
-            "do not initialize, if initialize method is inherited"
-            (eachLoadedClass theMetaclass includesSelector:#initialize) ifTrue:[
-                eachLoadedClass initialize
-            ].
-        ].
-        ^ true.
+	loadedClasses := OrderedCollection new.
+
+	self packageDirectory isNil ifTrue:[
+	    self
+		error:(self name,'[error] cannot install because packageDirectory is unknown')
+		mayProceed:true.
+	    ^ false.
+	].
+
+	"we need the abbreviations, since sometimes there is no 1-to-1 mapping
+	 of class name to file name"
+
+	Smalltalk recursiveReadAllAbbreviationsFrom:self packageDirectory maxLevels:1.
+
+	"install autoloaded classes first,
+	 some others may depend on them"
+
+	classNamesToAutoload withIndexDo:[:eachClassName :index|
+	    ActivityNotification
+		raiseRequestWith: ((100 / classNamesToAutoload size ) * index) rounded
+		errorString: 'Autoloading class ', eachClassName.
+
+	    Smalltalk
+		installAutoloadedClassNamed:eachClassName
+		category:#autoloaded    "FIXME"
+		package:self package
+		revision:nil
+		numClassInstVars:0.     "FIXME"
+	].
+
+	classesWhichFailedToLoad := OrderedCollection new.
+	classNamesToLoad notEmpty ifTrue:[
+	    Verbose ifTrue:[
+		Transcript showCR:('  %1: filing in missing classes (%2) individually...'
+				    bindWith:self name with:classNamesToLoad size).
+	    ]
+	].
+	classNamesToLoad withIndexDo:[:eachClassName :index|
+	    |cls|
+	    ActivityNotification
+		raiseRequestWith: ((100 / classNamesToLoad size) * index) rounded
+		errorString: 'Loading class ', eachClassName.
+
+	    Error handle:[:ex |
+		"maybe, fileIn failed, because the load order is wrong.
+		 Work around this by installing the class as autoloaded and
+		 loading it"
+
+		classesWhichFailedToLoad add:eachClassName.
+		Smalltalk
+		    installAutoloadedClassNamed:eachClassName
+		    category:#autoloaded    "FIXME"
+		    package:self package
+		    revision:nil
+		    numClassInstVars:0.     "FIXME"
+	    ] do:[
+		Verbose ifTrue:[
+		    Transcript showCR:('  %1: filing in %2...' bindWith:self name with:eachClassName).
+		].
+		cls := Smalltalk
+			    fileInClass:eachClassName
+			    package:self package
+			    initialize:false
+			    lazy:false
+			    silent:true.
+		cls notNil ifTrue:[
+		    loadedClasses add:cls
+		].
+	    ].
+	].
+
+	classesWhichFailedToLoad do:[:eachClassName |
+	    (Smalltalk at:eachClassName) autoload.
+	].
+
+	loadedClasses do:[:eachLoadedClass |
+	    "do not initialize, if initialize method is inherited"
+	    (eachLoadedClass theMetaclass includesSelector:#initialize) ifTrue:[
+		eachLoadedClass initialize
+	    ].
+	].
+	^ true.
     ].
     ^ false.
 
@@ -7048,13 +7048,13 @@
     "unload other packages"
 
     self effectiveSubProjects do:[:p |
-        |subDef|
-
-        subDef := self definitionClassForPackage:p.
-        subDef notNil ifTrue:[
-            subDef unloadSubProjects.
-            subDef unloadPackage.
-        ].
+	|subDef|
+
+	subDef := self definitionClassForPackage:p.
+	subDef notNil ifTrue:[
+	    subDef unloadSubProjects.
+	    subDef unloadPackage.
+	].
     ].
 !
 
@@ -7063,7 +7063,7 @@
      May be some more classes have to be loaded"
 
     (changedObject == self class and:[anAspectSymbol == #methodDictionary]) ifTrue:[
-        self projectIsLoaded:false.
+	self projectIsLoaded:false.
     ]
 ! !
 
@@ -7073,19 +7073,19 @@
     "helper for searchForPreRequisites"
 
     aSetOfClasses
-        do:[:aClass |
-            self
-                addReferencesToClassesFromGlobalsInMethods:
-                    (aClass theNonMetaclass methodDictionary values
-                        reject:[:m | m isExtension])
-                to:usedClassReasons.
-
-            self
-                addReferencesToClassesFromGlobalsInMethods:
-                    (aClass theMetaclass methodDictionary values
-                        reject:[:m | m isExtension])
-                to:usedClassReasons.
-        ].
+	do:[:aClass |
+	    self
+		addReferencesToClassesFromGlobalsInMethods:
+		    (aClass theNonMetaclass methodDictionary values
+			reject:[:m | m isExtension])
+		to:usedClassReasons.
+
+	    self
+		addReferencesToClassesFromGlobalsInMethods:
+		    (aClass theMetaclass methodDictionary values
+			reject:[:m | m isExtension])
+		to:usedClassReasons.
+	].
 
     "Modified: / 10-10-2006 / 23:03:45 / cg"
 !
@@ -7094,27 +7094,27 @@
     "helper for searchForPreRequisites"
 
     someMethods do:[:method |
-        |resources|
-
-        resources := method resources.
-        (resources isNil
-        or:[ ((resources includesKey:#'ignoreInPrerequisites') not
-              and:[(resources includesKey:#'example') not])])
-        ifTrue:[
-            method usedGlobals
-                do:[:global |
-                    |globalsName usedClass|
-
-                    globalsName := global asSymbol.
-                    usedClass := Smalltalk at:globalsName.
-                    (usedClass notNil and:[usedClass isClass and:[usedClass isNameSpace not]]) ifTrue:[
-                        usedClass name == globalsName ifTrue:[ "/ skip aliases
-                            (usedClassReasons at:usedClass ifAbsentPut:[Set new])
-                                add:(usedClass name, ' - referenced by ', method mclass name,'>>',method selector)
-                        ]
-                    ]
-                ]
-            ]
+	|resources|
+
+	resources := method resources.
+	(resources isNil
+	or:[ ((resources includesKey:#'ignoreInPrerequisites') not
+	      and:[(resources includesKey:#'example') not])])
+	ifTrue:[
+	    method usedGlobals
+		do:[:global |
+		    |globalsName usedClass|
+
+		    globalsName := global asSymbol.
+		    usedClass := Smalltalk at:globalsName.
+		    (usedClass notNil and:[usedClass isClass and:[usedClass isNameSpace not]]) ifTrue:[
+			usedClass name == globalsName ifTrue:[ "/ skip aliases
+			    (usedClassReasons at:usedClass ifAbsentPut:[Set new])
+				add:(usedClass name, ' - referenced by ', method mclass name,'>>',method selector)
+			]
+		    ]
+		]
+	    ]
     ]
 
     "Created: / 10-10-2006 / 23:00:07 / cg"
@@ -7131,28 +7131,28 @@
 
     "/ only care for methods which are not already implemented in an extension methods's superclass
     allRealExtensions := Smalltalk allExtensions
-                            select:[:mthd |
-                                |superClass|
-                                superClass := mthd mclass superclass.
-                                (superClass isNil or:[superClass whichClassIncludesSelector:mthd selector]) isNil
-                            ].
+			    select:[:mthd |
+				|superClass|
+				superClass := mthd mclass superclass.
+				(superClass isNil or:[superClass whichClassIncludesSelector:mthd selector]) isNil
+			    ].
 
     someClasses do:[:eachClass |
-        eachClass instAndClassMethodsDo:[:method |
-            |resources extensionsSent|
-
-            resources := method resources.
-            (resources isNil
-            or:[ ((resources includesKey:#'ignoreInPrerequisites') not
-                  and:[(resources includesKey:#'example') not])])
-            ifTrue:[
-                extensionsSent := allRealExtensions select:[:ext | method messagesSent includes:ext selector].
-                extensionsSent do:[:eachExtensionMethod |
-                    (usedMethodReasons at:eachExtensionMethod ifAbsentPut:[Set new])
-                        add:(eachExtensionMethod selector, ' - sent by ', method mclass name,'>>',method selector)
-                ]
-            ]
-        ]
+	eachClass instAndClassMethodsDo:[:method |
+	    |resources extensionsSent|
+
+	    resources := method resources.
+	    (resources isNil
+	    or:[ ((resources includesKey:#'ignoreInPrerequisites') not
+		  and:[(resources includesKey:#'example') not])])
+	    ifTrue:[
+		extensionsSent := allRealExtensions select:[:ext | method messagesSent includes:ext selector].
+		extensionsSent do:[:eachExtensionMethod |
+		    (usedMethodReasons at:eachExtensionMethod ifAbsentPut:[Set new])
+			add:(eachExtensionMethod selector, ' - sent by ', method mclass name,'>>',method selector)
+		]
+	    ]
+	]
     ]
 !
 
@@ -7162,10 +7162,10 @@
     ^ self allPreRequisites:#effectiveMandatoryPreRequisites.
 
     "
-     stx_libbasic allMandatoryPreRequisites 
+     stx_libbasic allMandatoryPreRequisites
      stx_libbasic2 allMandatoryPreRequisites
-     stx_libview2 allMandatoryPreRequisites 
-     stx_libcomp allMandatoryPreRequisites  
+     stx_libview2 allMandatoryPreRequisites
+     stx_libcomp allMandatoryPreRequisites
     "
 
     "Created: / 06-06-2016 / 12:19:39 / cg"
@@ -7173,13 +7173,13 @@
 
 allMandatoryPreRequisitesSorted
     [
-        ^ self allPreRequisitesSorted:#effectiveMandatoryPreRequisites
+	^ self allPreRequisitesSorted:#effectiveMandatoryPreRequisites
     ] on:Error do:[:ex |
-        (self confirm:(self name,' [warning]: cycle in prerequisites:' ,, Character cr, '    ', (ex parameter printStringWithSeparator:' -> ') ,, Character cr,  'Proceed with incomplete (mandatory) prerequites?'))
-        ifFalse:[
-            AbortOperationRequest raise
-        ].
-        ^ self allPreRequisitesSorted:#mandatoryPreRequisites
+	(self confirm:(self name,' [warning]: cycle in prerequisites:' ,, Character cr, '    ', (ex parameter printStringWithSeparator:' -> ') ,, Character cr,  'Proceed with incomplete (mandatory) prerequites?'))
+	ifFalse:[
+	    AbortOperationRequest raise
+	].
+	^ self allPreRequisitesSorted:#mandatoryPreRequisites
     ].
 
     "Created: / 06-06-2016 / 12:20:40 / cg"
@@ -7209,11 +7209,11 @@
     |result|
 
     result := self
-        allPreRequisites:aSelector withParentDo:[:parent :prereq |
-            prereq = self package ifTrue:[
-                Transcript showCR:('oops: %1 depends on itself' bindWith:prereq)
-            ].
-        ].
+	allPreRequisites:aSelector withParentDo:[:parent :prereq |
+	    prereq = self package ifTrue:[
+		Transcript showCR:('oops: %1 depends on itself' bindWith:prereq)
+	    ].
+	].
     result remove:self package ifAbsent:[].
     ^ result.
 
@@ -7247,27 +7247,27 @@
 "/    toAdd addAll:self effectiveSubProjects.
 
     [toAdd notEmpty] whileTrue:[
-        |aPreRequisiteProjectID def|
-
-        aPreRequisiteProjectID := toAdd removeFirst.
-        (setOfAllPreRequisites includes:aPreRequisiteProjectID) ifFalse:[
-            setOfAllPreRequisites add:aPreRequisiteProjectID.
-
-            def := self definitionClassForPackage:aPreRequisiteProjectID.
-            def isNil ifTrue:[
-                Transcript showCR:'ProjectDefinition ', aPreRequisiteProjectID, ' is missing - cannot find its preRequisites.'.
-            ] ifFalse:[
-                (def perform:aSelector)
-                    select:[:eachSubPreRequisite | (setOfAllPreRequisites includes:eachSubPreRequisite) not]
-                    thenDo:[:eachSubPreRequisite |
-                                Verbose == true ifTrue:[
-                                    Transcript show:'ProjectDefinition preRequisites: '; showCR:(aPreRequisiteProjectID, ' requires ', eachSubPreRequisite).
-                                ].
-                                aBlock value:def value:eachSubPreRequisite.
-                                toAdd add:eachSubPreRequisite
-                           ].
-
-                "but subprojects of our prerequisites are also prerequisites"
+	|aPreRequisiteProjectID def|
+
+	aPreRequisiteProjectID := toAdd removeFirst.
+	(setOfAllPreRequisites includes:aPreRequisiteProjectID) ifFalse:[
+	    setOfAllPreRequisites add:aPreRequisiteProjectID.
+
+	    def := self definitionClassForPackage:aPreRequisiteProjectID.
+	    def isNil ifTrue:[
+		Transcript showCR:'ProjectDefinition ', aPreRequisiteProjectID, ' is missing - cannot find its preRequisites.'.
+	    ] ifFalse:[
+		(def perform:aSelector)
+		    select:[:eachSubPreRequisite | (setOfAllPreRequisites includes:eachSubPreRequisite) not]
+		    thenDo:[:eachSubPreRequisite |
+				Verbose == true ifTrue:[
+				    Transcript show:'ProjectDefinition preRequisites: '; showCR:(aPreRequisiteProjectID, ' requires ', eachSubPreRequisite).
+				].
+				aBlock value:def value:eachSubPreRequisite.
+				toAdd add:eachSubPreRequisite
+			   ].
+
+		"but subprojects of our prerequisites are also prerequisites"
 "/ SV: - I don't think so. Either we need them, because they have classes being superclasses
 "/ or referenced. Or we include the explicitly. In both cases we do not need this code.
 "/ But we do not want them only because there is a subProject with examples or tests!!
@@ -7281,8 +7281,8 @@
 "/                                aBlock value:def value:eachSubSubRequisite.
 "/                                toAdd add:eachSubSubRequisite
 "/                           ].
-            ].
-        ]
+	    ].
+	]
     ].
     ^ setOfAllPreRequisites.
 
@@ -7303,13 +7303,13 @@
 
 allPreRequisitesSorted
     [
-        ^ self allPreRequisitesSorted:#effectivePreRequisites
+	^ self allPreRequisitesSorted:#effectivePreRequisites
     ] on:Error do:[:ex |
-        (self confirm:(self name,' [warning]: cycle in prerequisites:' ,, Character cr, '    ', (ex parameter printStringWithSeparator:' -> ') ,, Character cr,  'Proceed with incomplete (only mandatory) prerequites?'))
-        ifFalse:[
-            AbortOperationRequest raise
-        ].
-        ^ self allPreRequisitesSorted:#mandatoryPreRequisites
+	(self confirm:(self name,' [warning]: cycle in prerequisites:' ,, Character cr, '    ', (ex parameter printStringWithSeparator:' -> ') ,, Character cr,  'Proceed with incomplete (only mandatory) prerequites?'))
+	ifFalse:[
+	    AbortOperationRequest raise
+	].
+	^ self allPreRequisitesSorted:#mandatoryPreRequisites
     ].
 
     "Modified: / 21-02-2017 / 17:53:35 / cg"
@@ -7329,28 +7329,28 @@
     "/JV@2013-03-13: Added asSortedCollection to make the order of packages
     "/as stable as possible. Makes merging of makefiles a lot easier.
     allPreRequisites asSortedCollection do:[:eachPackageID |
-        |def preRequisites|
-
-        self assert:(eachPackageID ~= self package).
-        orderedTuples add:(Array with:eachPackageID with:self package).
-
-        def := self definitionClassForPackage:eachPackageID.
-        def isNil ifTrue:[
-            Transcript showCR:'Warning: no definition class for package: ', eachPackageID.
-            ((self searchForPreRequisites: eachPackageID)
-                fold:[:d1 :d2| d1 addAll:d2; yourself]) keys
-        ] ifFalse:[
-            preRequisites := def perform:aSelector.
-            preRequisites := preRequisites copyWithoutAll:def excludedFromPreRequisites.
-            preRequisites do:[:eachPrerequisitePackageID|
-                self assert:(eachPrerequisitePackageID ~= eachPackageID).
-                orderedTuples add:(Array with:eachPrerequisitePackageID with:eachPackageID).
-            ].
-        ].
+	|def preRequisites|
+
+	self assert:(eachPackageID ~= self package).
+	orderedTuples add:(Array with:eachPackageID with:self package).
+
+	def := self definitionClassForPackage:eachPackageID.
+	def isNil ifTrue:[
+	    Transcript showCR:'Warning: no definition class for package: ', eachPackageID.
+	    ((self searchForPreRequisites: eachPackageID)
+		fold:[:d1 :d2| d1 addAll:d2; yourself]) keys
+	] ifFalse:[
+	    preRequisites := def perform:aSelector.
+	    preRequisites := preRequisites copyWithoutAll:def excludedFromPreRequisites.
+	    preRequisites do:[:eachPrerequisitePackageID|
+		self assert:(eachPrerequisitePackageID ~= eachPackageID).
+		orderedTuples add:(Array with:eachPrerequisitePackageID with:eachPackageID).
+	    ].
+	].
     ].
 
     (orderedTuples contains:[:el | el first = el second]) ifTrue:[
-        self halt:'something seems to depend upon itself'
+	self halt:'something seems to depend upon itself'
     ].
     sortedPackages := orderedTuples topologicalSortStable: true.
 
@@ -7380,7 +7380,7 @@
     mandatory := self allMandatoryPreRequisitesSorted.
     pre := OrderedSet withAll:mandatory.
     self allPreRequisites do:[:each |
-        (mandatory includes:each) ifFalse:[ pre add: each ]
+	(mandatory includes:each) ifFalse:[ pre add: each ]
     ].
     ^ pre
 
@@ -7393,11 +7393,11 @@
     |result|
 
     result := self
-        allPreRequisites:#referencedPreRequisites withParentDo:[:parent :prereq |
-            prereq = self package ifTrue:[
-                Transcript showCR:('oops: %1 depends on itself' bindWith:prereq)
-            ].
-        ].
+	allPreRequisites:#referencedPreRequisites withParentDo:[:parent :prereq |
+	    prereq = self package ifTrue:[
+		Transcript showCR:('oops: %1 depends on itself' bindWith:prereq)
+	    ].
+	].
     result remove:self package ifAbsent:[].
     ^ result.
 
@@ -7418,23 +7418,23 @@
      and compiling (i.e. which must be present BEFORE)"
 
     self mandatoryPreRequisites notEmpty ifTrue:[
-        "this is a new subclass - avoid overhead"
-        ^ OrderedSet new
-            addAll:self mandatoryPreRequisites;
-            "/ addAll:self includedInPreRequisites;
-            removeAllFoundIn:self excludedFromMandatoryPreRequisites;
-            removeAllFoundIn:self excludedFromPreRequisites;
-            yourself.
+	"this is a new subclass - avoid overhead"
+	^ OrderedSet new
+	    addAll:self mandatoryPreRequisites;
+	    "/ addAll:self includedInPreRequisites;
+	    removeAllFoundIn:self excludedFromMandatoryPreRequisites;
+	    removeAllFoundIn:self excludedFromPreRequisites;
+	    yourself.
     ].
 
     "I am an old subclass, where #preRequisites returns a plain array"
     ^ Set new
-        addAll:self preRequisites;
-        addAll:self includedInPreRequisites;
-        removeAllFoundIn:self excludedFromMandatoryPreRequisites;
-        removeAllFoundIn:self excludedFromPreRequisites;
-        remove:self package ifAbsent:[];
-        yourself.
+	addAll:self preRequisites;
+	addAll:self includedInPreRequisites;
+	removeAllFoundIn:self excludedFromMandatoryPreRequisites;
+	removeAllFoundIn:self excludedFromPreRequisites;
+	remove:self package ifAbsent:[];
+	yourself.
 !
 
 effectivePreRequisites
@@ -7444,17 +7444,17 @@
      But is to be kept for backward compatibilty with old existing subclasses."
 
     self mandatoryPreRequisites notEmpty ifTrue:[
-        "this is a new subclass - avoid overhead"
-        ^ self preRequisites.
+	"this is a new subclass - avoid overhead"
+	^ self preRequisites.
     ].
 
     "I am an old subclass, where #preRequisites returns a plain array"
     ^ Set new
-        addAll:self preRequisites;
-        addAll:self includedInPreRequisites;
-        removeAllFoundIn:self excludedFromPreRequisites;
-        remove:self package ifAbsent:[];
-        yourself.
+	addAll:self preRequisites;
+	addAll:self includedInPreRequisites;
+	removeAllFoundIn:self excludedFromPreRequisites;
+	remove:self package ifAbsent:[];
+	yourself.
 !
 
 searchForPreRequisites
@@ -7515,10 +7515,10 @@
     requiredClasses := self searchForClassesWithProject: packageId.
 
     withSubProjectsBoolean ifTrue:[
-        "my subproject's classes are required"
-        self effectiveSubProjects do:[:eachProjectName |
-            requiredClasses addAll:(self searchForClassesWithProject:eachProjectName asSymbol)
-        ].
+	"my subproject's classes are required"
+	self effectiveSubProjects do:[:eachProjectName |
+	    requiredClasses addAll:(self searchForClassesWithProject:eachProjectName asSymbol)
+	].
     ].
 
     "/ ..but not if they're a Java class
@@ -7528,35 +7528,35 @@
      and my subProject's classes (if required) are mandatory.
      All shared pools used by my classes are required as well"
     requiredClasses do:[:cls |
-        (self autoloaded_classNames includes:cls name) ifFalse:[
-            cls allSuperclassesDo:[:eachSuperclass |
-                (mandatoryClassesForLoadingWithReasons at: eachSuperclass ifAbsentPut:[OrderedSet new])
-                    add: (eachSuperclass name, ' - superclass of ', cls name).
-            ].
-        ].
-        cls sharedPools do:[:eachSharedPool |
-            (mandatoryClassesForLoadingWithReasons at: eachSharedPool ifAbsentPut:[OrderedSet new])
-                add: (eachSharedPool name, ' - shared pool used by ', cls name).
-            eachSharedPool allSuperclassesDo:[:eachSuperclass |
-                (mandatoryClassesForLoadingWithReasons at: eachSuperclass ifAbsentPut:[OrderedSet new])
-                    add: (eachSuperclass name, ' - superclass of shared pool ', eachSharedPool name).
-            ]
-        ]
+	(self autoloaded_classNames includes:cls name) ifFalse:[
+	    cls allSuperclassesDo:[:eachSuperclass |
+		(mandatoryClassesForLoadingWithReasons at: eachSuperclass ifAbsentPut:[OrderedSet new])
+		    add: (eachSuperclass name, ' - superclass of ', cls name).
+	    ].
+	].
+	cls sharedPools do:[:eachSharedPool |
+	    (mandatoryClassesForLoadingWithReasons at: eachSharedPool ifAbsentPut:[OrderedSet new])
+		add: (eachSharedPool name, ' - shared pool used by ', cls name).
+	    eachSharedPool allSuperclassesDo:[:eachSuperclass |
+		(mandatoryClassesForLoadingWithReasons at: eachSuperclass ifAbsentPut:[OrderedSet new])
+		    add: (eachSuperclass name, ' - superclass of shared pool ', eachSharedPool name).
+	    ]
+	]
     ].
     "all classes for which I define extensions are mandatory"
     self allExtensionClasses do:[:eachExtendedClass |
-        (mandatoryClassesForLoadingWithReasons at:eachExtendedClass ifAbsentPut:[OrderedSet new])
-            add: (eachExtendedClass name, ' - extended').
-        eachExtendedClass allSuperclassesDo:[:eachSuperclass |
-            (mandatoryClassesForLoadingWithReasons at: eachSuperclass ifAbsentPut:[OrderedSet new])
-                add: (eachSuperclass name, ' - superclass of extended ', eachExtendedClass name).
-        ]
+	(mandatoryClassesForLoadingWithReasons at:eachExtendedClass ifAbsentPut:[OrderedSet new])
+	    add: (eachExtendedClass name, ' - extended').
+	eachExtendedClass allSuperclassesDo:[:eachSuperclass |
+	    (mandatoryClassesForLoadingWithReasons at: eachSuperclass ifAbsentPut:[OrderedSet new])
+		add: (eachSuperclass name, ' - superclass of extended ', eachExtendedClass name).
+	]
     ].
 
     "all classes referenced by my classes or my subproject's classes
      are required. But:
-         only search for locals refered to by my methods (assuming that superclasses'
-         prerequisites are specified in their package)."
+	 only search for locals refered to by my methods (assuming that superclasses'
+	 prerequisites are specified in their package)."
 
     self addReferencesToClassesFromGlobalsIn:requiredClasses to:referencedClassesWithReasons.
     self addReferencesToClassesFromGlobalsInMethods:(self searchForExtensionsWithProject:self package) to:referencedClassesWithReasons.
@@ -7564,16 +7564,16 @@
 
     "now map classes to packages and collect the reasons"
     packageExtractionBlock :=
-        [:classesWithReasons|
-            |requiredPackageReasons|
-            requiredPackageReasons := Dictionary new.
-            classesWithReasons keysAndValuesDo:[:usedClass :reasonsPerClass|
-                (requiredPackageReasons at:usedClass package ifAbsentPut:[Set new])
-                                addAll:reasonsPerClass.
-            ].
-            "sort, to avoid differences from one generation to the next one"
-            requiredPackageReasons
-        ].
+	[:classesWithReasons|
+	    |requiredPackageReasons|
+	    requiredPackageReasons := Dictionary new.
+	    classesWithReasons keysAndValuesDo:[:usedClass :reasonsPerClass|
+		(requiredPackageReasons at:usedClass package ifAbsentPut:[Set new])
+				addAll:reasonsPerClass.
+	    ].
+	    "sort, to avoid differences from one generation to the next one"
+	    requiredPackageReasons
+	].
 
     mandatoryPackageReasons := packageExtractionBlock value:mandatoryClassesForLoadingWithReasons.
 
@@ -7581,13 +7581,13 @@
 
     "and map extension method invocations to packages and collect the reasons"
     referencedMethodsWithReasons keysAndValuesDo:[:usedMethod :reasonsPerMethod |
-        (referencedPackageReasons at:usedMethod package ifAbsentPut:[Set new])
-            addAll:reasonsPerMethod.
+	(referencedPackageReasons at:usedMethod package ifAbsentPut:[Set new])
+	    addAll:reasonsPerMethod.
     ].
 
     ignoredPackages := Set
-        with:packageId
-        with:PackageId noProjectID.
+	with:packageId
+	with:PackageId noProjectID.
 
     referencedPackageReasons removeAllKeys:ignoredPackages ifAbsent:[].
     "sort, to avoid differences from one generation to the next one"
@@ -7595,16 +7595,16 @@
 
     "don't put classes from subProjects into the required list"
     ignoredPackages addAll:(self siblingsAreSubProjects
-                                ifTrue:[ self searchForSiblingProjects ]
-                                ifFalse:[ self searchForSubProjects ]) asSet.
+				ifTrue:[ self searchForSiblingProjects ]
+				ifFalse:[ self searchForSubProjects ]) asSet.
 
     mandatoryPackageReasons removeAllKeys:ignoredPackages ifAbsent:[].
     "sort, to avoid differences from one generation to the next one"
     mandatoryPackageReasons keysAndValuesDo:[:eachPackageId :eachReasons | mandatoryPackageReasons at:eachPackageId put:eachReasons asSortedCollection].
 
     ^ Array
-        with:mandatoryPackageReasons
-        with:referencedPackageReasons.
+	with:mandatoryPackageReasons
+	with:referencedPackageReasons.
 
     "
      self searchForPreRequisites:#'stx:libwidg3'
@@ -7628,16 +7628,16 @@
 
 allClasses
     ^ self allClassNames
-        collect:[:nm |
-            |cls|
-
-            cls := Smalltalk classNamed:nm.
-            cls isNil ifTrue:[
-                Logger warning:'%1: failed to autoload class %2' with:self name with:nm
-            ].
-            cls
-        ]
-        thenSelect:[:cls | cls notNil ].
+	collect:[:nm |
+	    |cls|
+
+	    cls := Smalltalk classNamed:nm.
+	    cls isNil ifTrue:[
+		Logger warning:'%1: failed to autoload class %2' with:self name with:nm
+	    ].
+	    cls
+	]
+	thenSelect:[:cls | cls notNil ].
 
     "Created: / 06-08-2011 / 15:47:36 / cg"
 !
@@ -7695,9 +7695,9 @@
 
     coll := OrderedCollection new.
     self classNamesAndAttributesDo:[:nm :attributes |
-        (aBlock value:nm value:attributes) ifTrue:[
-            coll add:nm.
-        ].
+	(aBlock value:nm value:attributes) ifTrue:[
+	    coll add:nm.
+	].
     ].
     ^ coll
 
@@ -7743,9 +7743,9 @@
      platformName is one of #unix, #win32, #vms or #osx (OperatingSystem platformName)"
 
     ^ self
-        classNamesForWhich:[:nm :attr |
-            (attr includes:#autoload) not and:[attr includes:platformName]
-        ].
+	classNamesForWhich:[:nm :attr |
+	    (attr includes:#autoload) not and:[attr includes:platformName]
+	].
 
     "Created: / 07-08-2006 / 19:02:57 / fm"
     "Modified: / 07-08-2006 / 21:25:25 / fm"
@@ -7756,9 +7756,9 @@
     "classes to be compiled for any platform"
 
     ^ self
-        classNamesForWhich:[:nm :attr |
-            attr isEmptyOrNil
-        ].
+	classNamesForWhich:[:nm :attr |
+	    attr isEmptyOrNil
+	].
 
     "Created: / 18-08-2006 / 13:37:51 / cg"
 !
@@ -7784,8 +7784,8 @@
      Project must be loaded - otherwise an error is reported here.
      Use #classNames if you are only interested in the names"
 
-    ^ self compiled_classNamesForPlatform collect:[:nm | 
-            Smalltalk at:nm ifAbsent:[self error:'Missing class: ',nm]]
+    ^ self compiled_classNamesForPlatform collect:[:nm |
+	    Smalltalk at:nm ifAbsent:[self error:'Missing class: ',nm]]
 
     "
      stx_libbasic compiled_classesForPlatform
@@ -7813,26 +7813,26 @@
     classes := IdentitySet new.
 
     self extensionMethodNames pairWiseDo:[:className :selector |
-        |mthdCls extendedClass|
-
-        mthdCls := Smalltalk classNamed:className.
-        (mthdCls notNil and:[mthdCls isLoaded]) ifTrue:[
-            extendedClass := mthdCls theNonMetaclass.
-            (classes includes:extendedClass) ifFalse:[
-                withSuperclassesBoolean ifTrue:[
-                    extendedClass withAllSuperclassesDo:[:eachClass |
-                        classes add:eachClass.
-                    ].
-                ] ifFalse:[
-                    classes add:extendedClass.
-                ].
-            ].
-        ].
+	|mthdCls extendedClass|
+
+	mthdCls := Smalltalk classNamed:className.
+	(mthdCls notNil and:[mthdCls isLoaded]) ifTrue:[
+	    extendedClass := mthdCls theNonMetaclass.
+	    (classes includes:extendedClass) ifFalse:[
+		withSuperclassesBoolean ifTrue:[
+		    extendedClass withAllSuperclassesDo:[:eachClass |
+			classes add:eachClass.
+		    ].
+		] ifFalse:[
+		    classes add:extendedClass.
+		].
+	    ].
+	].
     ].
     ^ classes.
 
     "
-        stx_libboss extensionClasses
+	stx_libboss extensionClasses
     "
 
     "Created: / 06-09-2011 / 10:17:06 / cg"
@@ -7844,9 +7844,9 @@
      Use #extensionMethodsNames if you are only interested in the names"
 
     ^ self extensionMethodNames
-        pairWiseCollect:[:className :selector |
-            (Smalltalk classNamed:className) compiledMethodAt:selector.
-        ].
+	pairWiseCollect:[:className :selector |
+	    (Smalltalk classNamed:className) compiledMethodAt:selector.
+	].
 
     "
      stx_libbasic2 extensionMethodNames
@@ -7860,7 +7860,7 @@
     ^ self allExtensionClasses collect:[:eachClass| eachClass package]
 
     "
-        stx_libboss extensionPackages
+	stx_libboss extensionPackages
     "
 
     "Modified: / 06-09-2011 / 10:20:47 / cg"
@@ -7887,12 +7887,12 @@
      If checkIfFullyLoaded is true, they must be fully loaded; that means: not autoloaded"
 
     ^ (self
-            hasClasses:(self classNamesForWhich:[:nm :attr | attr isEmptyOrNil or:[ attr includes:#autoload]])
-            loaded:checkIfFullyLoaded)
+	    hasClasses:(self classNamesForWhich:[:nm :attr | attr isEmptyOrNil or:[ attr includes:#autoload]])
+	    loaded:checkIfFullyLoaded)
     and:[
-        self
-            hasClasses:(self compiled_classNamesForPlatform:OperatingSystem platformName)
-            loaded:checkIfFullyLoaded ]
+	self
+	    hasClasses:(self compiled_classNamesForPlatform:OperatingSystem platformName)
+	    loaded:checkIfFullyLoaded ]
 
     "Modified: / 07-11-2006 / 11:47:30 / cg"
 !
@@ -7910,12 +7910,12 @@
      If checkIfFullyLoaded is true, they must be fully loaded, that is not autoloaded"
 
     ^ (self
-            hasClasses:(self classNamesForWhich:[:nm :attr | attr isEmptyOrNil])
-            loaded:checkIfFullyLoaded)
+	    hasClasses:(self classNamesForWhich:[:nm :attr | attr isEmptyOrNil])
+	    loaded:checkIfFullyLoaded)
     and:[
        self
-            hasClasses:(self compiled_classNamesForPlatform:OperatingSystem platformName)
-            loaded:checkIfFullyLoaded
+	    hasClasses:(self compiled_classNamesForPlatform:OperatingSystem platformName)
+	    loaded:checkIfFullyLoaded
     ]
 !
 
@@ -7924,22 +7924,22 @@
      This is a query - so no side effects please"
 
     (self extensionMethodNames ? #()) pairWiseDo:[:className :selector |
-        |cls|
-
-        cls := Smalltalk loadedClassNamed:className.
-        cls isNil ifTrue:[
-            Verbose ifTrue:[
-                Transcript showCR:(self name,' missing extension class "',className,'".').
-            ].
-            ^ false
-        ].
-        "there is no possibility that we installed an extension method in an unloaded class"
-        (cls isLoaded not or:[(cls compiledMethodAt:selector) isNil]) ifTrue:[
-            Verbose ifTrue:[
-                Transcript showCR:(self name,' missing extension method "',className,'>>',selector,'".').
-            ].
-            ^ false
-        ].
+	|cls|
+
+	cls := Smalltalk loadedClassNamed:className.
+	cls isNil ifTrue:[
+	    Verbose ifTrue:[
+		Transcript showCR:(self name,' missing extension class "',className,'".').
+	    ].
+	    ^ false
+	].
+	"there is no possibility that we installed an extension method in an unloaded class"
+	(cls isLoaded not or:[(cls compiledMethodAt:selector) isNil]) ifTrue:[
+	    Verbose ifTrue:[
+		Transcript showCR:(self name,' missing extension method "',className,'>>',selector,'".').
+	    ].
+	    ^ false
+	].
     ].
     ^ true.
 
@@ -7953,21 +7953,21 @@
      are not considered"
 
     classNames do:[:eachClassName |
-        |cls|
-
-        cls := Smalltalk loadedClassNamed:eachClassName.
-        cls isNil ifTrue:[
-            Verbose ifTrue:[
-               (self name, ' [info]: missing class: ', eachClassName) infoPrintCR.
-            ].
-            ^ false
-        ].
-        (checkIfFullyLoaded and:[cls isLoaded not]) ifTrue:[
-            Verbose ifTrue:[
-                (self name,' [info]: unloaded class: ', eachClassName) infoPrintCR.
-            ].
-            ^ false.
-        ].
+	|cls|
+
+	cls := Smalltalk loadedClassNamed:eachClassName.
+	cls isNil ifTrue:[
+	    Verbose ifTrue:[
+	       (self name, ' [info]: missing class: ', eachClassName) infoPrintCR.
+	    ].
+	    ^ false
+	].
+	(checkIfFullyLoaded and:[cls isLoaded not]) ifTrue:[
+	    Verbose ifTrue:[
+		(self name,' [info]: unloaded class: ', eachClassName) infoPrintCR.
+	    ].
+	    ^ false.
+	].
     ].
 
     ^ true
@@ -8008,14 +8008,14 @@
 isAutoloaded:aClassOrClassName
     |className|
 
-    className := aClassOrClassName isBehavior 
-                    ifTrue:[ aClassOrClassName theNonMetaclass name ]
-                    ifFalse:[ aClassOrClassName ].
+    className := aClassOrClassName isBehavior
+		    ifTrue:[ aClassOrClassName theNonMetaclass name ]
+		    ifFalse:[ aClassOrClassName ].
     ^ self autoloaded_classNames includes:className
 
     "
      'stx:goodies/soap/xe/tests' asPackageId projectDefinitionClass
-        isAutoloaded:#'SOAP::XeAllTests'
+	isAutoloaded:#'SOAP::XeAllTests'
     "
 !
 
@@ -8038,7 +8038,7 @@
     "answer false, if this package is not suitable for
      the current platform. The default here returns true.
      Only to be redefined in packages which are definitely not valid
-     for the given platform. For example, the OLE package is only 
+     for the given platform. For example, the OLE package is only
      usable under windows"
 
     ^ true
@@ -8052,9 +8052,9 @@
     referrers := OrderedCollection new.
 
     self allSubclassesDo:[:eachPackageDefinitionClass|
-        (eachPackageDefinitionClass allPreRequisites includes:aPackageString) ifTrue:[
-            referrers add:eachPackageDefinitionClass.
-        ]
+	(eachPackageDefinitionClass allPreRequisites includes:aPackageString) ifTrue:[
+	    referrers add:eachPackageDefinitionClass.
+	]
     ].
 
     ^ referrers.
@@ -8078,21 +8078,21 @@
     orderedTuples := OrderedCollection new.
 
     referers do:[:eachProjectDefinition |
-        |preRequisites|
-
-        preRequisites := eachProjectDefinition effectivePreRequisites.
-        preRequisites do:[:eachPrerequisitePackageID|
-            |eachPrerequisitePackage|
-
-            eachPrerequisitePackage := self definitionClassForPackage:eachPrerequisitePackageID.
-            (referers includes:eachPrerequisitePackage) ifTrue:[
-                orderedTuples add:(Array with:eachPrerequisitePackage with:eachProjectDefinition).
-            ].
-        ].
+	|preRequisites|
+
+	preRequisites := eachProjectDefinition effectivePreRequisites.
+	preRequisites do:[:eachPrerequisitePackageID|
+	    |eachPrerequisitePackage|
+
+	    eachPrerequisitePackage := self definitionClassForPackage:eachPrerequisitePackageID.
+	    (referers includes:eachPrerequisitePackage) ifTrue:[
+		orderedTuples add:(Array with:eachPrerequisitePackage with:eachProjectDefinition).
+	    ].
+	].
     ].
 
     (orderedTuples contains:[:el | el first = el second]) ifTrue:[
-        self halt:'something seems to depend upon itself'
+	self halt:'something seems to depend upon itself'
     ].
     sortedPackages := orderedTuples topologicalSortStable: true.
 
@@ -8132,27 +8132,27 @@
 
     emptyProjects := Set withAll:self effectiveSubProjects.
     Smalltalk allClassesDo:[:cls |
-        emptyProjects remove:(cls package) ifAbsent:[].
+	emptyProjects remove:(cls package) ifAbsent:[].
     ].
     nonProjects := self effectiveSubProjects select:[:p |
-                    (self definitionClassForPackage: p) isNil
-                   ].
+		    (self definitionClassForPackage: p) isNil
+		   ].
 
     emptyOrNonProjects := Set withAll:emptyProjects.
     emptyOrNonProjects addAll:nonProjects.
 
     emptyOrNonProjects notEmpty ifTrue:[
-        (Dialog
-            confirm:('The following subprojects are non-existent, empty or without description:\\    '
-                    , ((emptyOrNonProjects
-                            asSortedCollection
-                                collect:[:p | p allBold])
-                                asStringWith:'\    ')
-                    , '\\Continue ?') withCRs
-            yesLabel:'OK' noLabel:'Cancel')
-        ifFalse:[
-            AbortSignal raise
-        ].
+	(Dialog
+	    confirm:('The following subprojects are non-existent, empty or without description:\\    '
+		    , ((emptyOrNonProjects
+			    asSortedCollection
+				collect:[:p | p allBold])
+				asStringWith:'\    ')
+		    , '\\Continue ?') withCRs
+	    yesLabel:'OK' noLabel:'Cancel')
+	ifFalse:[
+	    AbortSignal raise
+	].
     ].
 
     myPackage := self package.
@@ -8162,70 +8162,70 @@
     ((self compiled_classNamesForPlatform:(OperatingSystem platformName))
     , (self compiled_classNames_common)
     , (self autoloaded_classNames)) do:[:nm |
-        |cls|
-
-        cls := Smalltalk at:nm asSymbol.
-        cls isNil ifTrue:[
-            (self autoloaded_classNames includes:nm) ifTrue:[
-                Transcript showCR:'missing autoloaded class: ',nm.
-            ] ifFalse:[
-                self proceedableError:('missing class: ',nm).
-            ]
-        ] ifFalse:[
-            classesInDescription add:cls.
-        ]
+	|cls|
+
+	cls := Smalltalk at:nm asSymbol.
+	cls isNil ifTrue:[
+	    (self autoloaded_classNames includes:nm) ifTrue:[
+		Transcript showCR:'missing autoloaded class: ',nm.
+	    ] ifFalse:[
+		self proceedableError:('missing class: ',nm).
+	    ]
+	] ifFalse:[
+	    classesInDescription add:cls.
+	]
     ].
 
     missingPools := Set new.
     classesInDescription do:[:eachClass |
-        eachClass sharedPoolNames do:[:eachPoolName |
-            |pool|
-
-            pool := eachClass nameSpace classNamed:eachPoolName.
-            pool isNil ifTrue:[
-                eachClass nameSpace ~~ Smalltalk ifTrue:[
-                    pool := Smalltalk classNamed:eachPoolName.
-                ]
-            ].
-            pool isNil ifTrue:[
-                Transcript showCR:'missing pool: ',eachPoolName.
-                missingPools add:eachPoolName.
-            ] ifFalse:[
-                pool isSharedPool ifFalse:[
-                    Transcript showCR:'not a shared pool: ',eachPoolName.
-                    missingPools add:eachPoolName.
-                ].
-            ].
-        ].
+	eachClass sharedPoolNames do:[:eachPoolName |
+	    |pool|
+
+	    pool := eachClass nameSpace classNamed:eachPoolName.
+	    pool isNil ifTrue:[
+		eachClass nameSpace ~~ Smalltalk ifTrue:[
+		    pool := Smalltalk classNamed:eachPoolName.
+		]
+	    ].
+	    pool isNil ifTrue:[
+		Transcript showCR:'missing pool: ',eachPoolName.
+		missingPools add:eachPoolName.
+	    ] ifFalse:[
+		pool isSharedPool ifFalse:[
+		    Transcript showCR:'not a shared pool: ',eachPoolName.
+		    missingPools add:eachPoolName.
+		].
+	    ].
+	].
     ].
 
     missingPools notEmpty ifTrue:[
-        (Dialog
-            confirm:('The following sharedpools are non-existent, or not pools:\\    '
-                    , ((missingPools
-                            asSortedCollection
-                                collect:[:p | p allBold])
-                                asStringWith:'\    ')
-                    , '\\Continue ?') withCRs
-            yesLabel:'OK' noLabel:'Cancel')
-        ifFalse:[
-            AbortOperationRequest raise
-        ].
+	(Dialog
+	    confirm:('The following sharedpools are non-existent, or not pools:\\    '
+		    , ((missingPools
+			    asSortedCollection
+				collect:[:p | p allBold])
+				asStringWith:'\    ')
+		    , '\\Continue ?') withCRs
+	    yesLabel:'OK' noLabel:'Cancel')
+	ifFalse:[
+	    AbortOperationRequest raise
+	].
     ].
 
 "/ also found by ProjectChecker...
     classesInImage ~= classesInDescription ifTrue:[
-        onlyInImage := (classesInImage reject:[:cls | classesInDescription includes:cls]).
-        onlyInImage notEmpty ifTrue:[
-            Transcript show:self name; show:': only in image: '; showCR:onlyInImage
-        ].
-        onlyInDescription := (classesInDescription reject:[:cls | classesInImage includes:cls]).
-        onlyInDescription notEmpty ifTrue:[
-            Transcript show:self name; show:': only in description: '; showCR:onlyInDescription
-        ].
-        (Dialog confirm:'The set of classes in the image is different from the listed classes in the project definition.\\Proceed?' withCRs) ifFalse:[
-            AbortOperationRequest raiseRequest
-        ]
+	onlyInImage := (classesInImage reject:[:cls | classesInDescription includes:cls]).
+	onlyInImage notEmpty ifTrue:[
+	    Transcript show:self name; show:': only in image: '; showCR:onlyInImage
+	].
+	onlyInDescription := (classesInDescription reject:[:cls | classesInImage includes:cls]).
+	onlyInDescription notEmpty ifTrue:[
+	    Transcript show:self name; show:': only in description: '; showCR:onlyInDescription
+	].
+	(Dialog confirm:'The set of classes in the image is different from the listed classes in the project definition.\\Proceed?' withCRs) ifFalse:[
+	    AbortOperationRequest raiseRequest
+	]
     ].
 
 "/    self validateOrderOfClasses
@@ -8250,30 +8250,30 @@
 
     classesInDescriptionInOrder := OrderedCollection new.
     classesInDescriptionInOrder :=
-        self compiled_classNames
-            collect:[:eachName |
-                |cls|
-
-                cls := Smalltalk at:eachName.
-                self assert:cls notNil message:'missing class: ',eachName.
-                cls
-            ].
+	self compiled_classNames
+	    collect:[:eachName |
+		|cls|
+
+		cls := Smalltalk at:eachName.
+		self assert:cls notNil message:'missing class: ',eachName.
+		cls
+	    ].
 
     classesInProject := classesInDescriptionInOrder asSet.
 
     already := Set new.
     classesInDescriptionInOrder do:[:eachClass |
-        eachClass allSuperclassesDo:[:superclass |
-            (classesInProject includes:superclass) ifTrue:[
-                "/ if in the set, it must have been already listed
-                self
-                    assert:(already includes:superclass)
-                    message:('superclass "%1" not compiled before "%2"'
-                                    bindWith:superclass name
-                                    with:eachClass name).
-            ].
-        ].
-        already add:eachClass.
+	eachClass allSuperclassesDo:[:superclass |
+	    (classesInProject includes:superclass) ifTrue:[
+		"/ if in the set, it must have been already listed
+		self
+		    assert:(already includes:superclass)
+		    message:('superclass "%1" not compiled before "%2"'
+				    bindWith:superclass name
+				    with:eachClass name).
+	    ].
+	].
+	already add:eachClass.
     ].
 
     "
@@ -8295,7 +8295,7 @@
 
 isConsoleApplication
     "Used with WIN32 only (i.e. affects bc.mak).
-     Return true, if this is a console application. 
+     Return true, if this is a console application.
      Console applications have stdout and stderr and open up a command-window
      when started. Only console applications can interact with the user in the
      command line window."
@@ -8373,15 +8373,15 @@
     methods in the projectDefinition to return a collection of instances of me.
 
     [author:]
-        cg
+	cg
 
     For example:
-        mimeType:  'application/x-expecco-testsuite
-        extension: 'ets'
-        typeName:  'expecco test suite'  
-        iconFileWindows:  'expeccoSuite.ico'  
-        iconFileOSX:      'expeccoSuite.icns'  
-        roleOSX:          'Editor'  
+	mimeType:  'application/x-expecco-testsuite
+	extension: 'ets'
+	typeName:  'expecco test suite'
+	iconFileWindows:  'expeccoSuite.ico'
+	iconFileOSX:      'expeccoSuite.icns'
+	roleOSX:          'Editor'
 "
 ! !
 
@@ -8389,7 +8389,7 @@
 
 extension
     "the extension of the document"
-    
+
     ^ extension
 !