changes to allow compilation under win32 (does not like strings beginning
authorClaus Gittinger <cg@exept.de>
Sat, 25 Sep 1999 15:20:37 +0200
changeset 4814 7825b9141f01
parent 4813 61b2c466896e
child 4815 75c3243e523a
changes to allow compilation under win32 (does not like strings beginning with a cr - how comes this ?)
Project.st
--- a/Project.st	Sat Sep 25 12:33:35 1999 +0200
+++ b/Project.st	Sat Sep 25 15:20:37 1999 +0200
@@ -58,35 +58,35 @@
     and define packageNames for new classes and methods.
 
     instance variables:
-        name            <String>        the name of this project, as shown
-                                        in a ProjectView
-
-        changeSet       <ChangeSet>     changes done, while this was the active project
-
-        views           <Collection>    views opened while this was the active project
-
-        directoryName   <String>        directory name, where fileOuts are done
-
-        properties 
-
-        packageName     <String>        given to classes/methods which are created while
-                                        this is the active project
-
-        repositoryDirectory             (default) name of the repository, when a new source containers are
-                                        created.
-
-        repositoryModule                (default) name of the module, when new source containers are
-                                        created.
+	name            <String>        the name of this project, as shown
+					in a ProjectView
+
+	changeSet       <ChangeSet>     changes done, while this was the active project
+
+	views           <Collection>    views opened while this was the active project
+
+	directoryName   <String>        directory name, where fileOuts are done
+
+	properties 
+
+	packageName     <String>        given to classes/methods which are created while
+					this is the active project
+
+	repositoryDirectory             (default) name of the repository, when a new source containers are
+					created.
+
+	repositoryModule                (default) name of the module, when new source containers are
+					created.
 
     Future: 
-        - keep track of per-project changes
-        - allow speficiation of the type of the project (application or library)
-        - allow building of whatever the target (as defined by the type) is
-          (this will allow build of class libs and apps by clicking a button)
-        - allow removal of project specific classes, methods etc.
+	- keep track of per-project changes
+	- allow speficiation of the type of the project (application or library)
+	- allow building of whatever the target (as defined by the type) is
+	  (this will allow build of class libs and apps by clicking a button)
+	- allow removal of project specific classes, methods etc.
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 ! !
 
@@ -105,98 +105,98 @@
     packages := Dictionary new.
 
     AllProjects isNil ifTrue:[
-        AllProjects := OrderedCollection new.
+	AllProjects := OrderedCollection new.
     ] ifFalse:[
-        AllProjects do:[:p | packages at:p package asSymbol put:p].
+	AllProjects do:[:p | packages at:p package asSymbol put:p].
     ].
     Smalltalk allClassesDo:[:aClass |
-        |packageID prj classFilename pkgInfo revInfo 
-         repositoryPath dir module lib nm|
-
-        aClass isMeta ifFalse:[
-            (aClass isNamespace not or:[aClass == Smalltalk]) ifTrue:[
-                packageID := aClass package asSymbol.
-                (packages includesKey:packageID) ifFalse:[
-
-                    "/ a new one ...
-
-                    prj := self new.
-                    prj package:packageID.
-                    prj directory:'???'.
-                    prj repositoryModule:'unknown'.
-                    prj repositoryDirectory:'unknown'.
-
-                    nm := 'unknown'.
-
-                    pkgInfo := aClass packageSourceCodeInfo.
-                    pkgInfo notNil ifTrue:[
-                        module := pkgInfo at:#module ifAbsent:nil.
-                        module notNil ifTrue:[
-                            prj repositoryModule:module    
-                        ].
-                        dir := pkgInfo at:#directory ifAbsent:nil.
-                        dir notNil ifTrue:[
-                            prj repositoryDirectory:dir    
-                        ].
-                        lib := pkgInfo at:#library ifAbsent:nil.
-                        lib notNil ifTrue:[
-                            prj type:#library.
-                        ].
-                        prj isLoaded:true.
-                    ].
-
-                    nm := (module ? 'unknown')
-                          , ':'
-                          , (dir ? (lib ? 'unknown')).
-                        
-                    prj name:nm.
-                    AllProjects add:prj.
-                    packages at:packageID put:prj.
-                ].
-            ].
-        ].
+	|packageID prj classFilename pkgInfo revInfo 
+	 repositoryPath dir module lib nm|
+
+	aClass isMeta ifFalse:[
+	    (aClass isNamespace not or:[aClass == Smalltalk]) ifTrue:[
+		packageID := aClass package asSymbol.
+		(packages includesKey:packageID) ifFalse:[
+
+		    "/ a new one ...
+
+		    prj := self new.
+		    prj package:packageID.
+		    prj directory:'???'.
+		    prj repositoryModule:'unknown'.
+		    prj repositoryDirectory:'unknown'.
+
+		    nm := 'unknown'.
+
+		    pkgInfo := aClass packageSourceCodeInfo.
+		    pkgInfo notNil ifTrue:[
+			module := pkgInfo at:#module ifAbsent:nil.
+			module notNil ifTrue:[
+			    prj repositoryModule:module    
+			].
+			dir := pkgInfo at:#directory ifAbsent:nil.
+			dir notNil ifTrue:[
+			    prj repositoryDirectory:dir    
+			].
+			lib := pkgInfo at:#library ifAbsent:nil.
+			lib notNil ifTrue:[
+			    prj type:#library.
+			].
+			prj isLoaded:true.
+		    ].
+
+		    nm := (module ? 'unknown')
+			  , ':'
+			  , (dir ? (lib ? 'unknown')).
+			
+		    prj name:nm.
+		    AllProjects add:prj.
+		    packages at:packageID put:prj.
+		].
+	    ].
+	].
     ].
     Method allSubInstancesDo:[:aMethod |
-        |packageID prj who mthdClass|
-
-        packageID := aMethod package asSymbol.
-        (packages includesKey:packageID) ifFalse:[
-            who := aMethod who.
-            who notNil ifTrue:[ "/ skip unbound methods ...
-                "/ a new one ...
-                prj := self new.
-        "/            prj name:libName.
-                prj package:packageID.
-                prj type:#library.
-                prj directory:'???'.
-                prj repositoryModule:'stx'.
-                prj repositoryDirectory:'???'.
-                prj isLoaded:true.
-                AllProjects add:prj.
-                packages at:packageID put:prj.
-            ]
-        ]
+	|packageID prj who mthdClass|
+
+	packageID := aMethod package asSymbol.
+	(packages includesKey:packageID) ifFalse:[
+	    who := aMethod who.
+	    who notNil ifTrue:[ "/ skip unbound methods ...
+		"/ a new one ...
+		prj := self new.
+	"/            prj name:libName.
+		prj package:packageID.
+		prj type:#library.
+		prj directory:'???'.
+		prj repositoryModule:'stx'.
+		prj repositoryDirectory:'???'.
+		prj isLoaded:true.
+		AllProjects add:prj.
+		packages at:packageID put:prj.
+	    ]
+	]
     ].
 
     "/ walk over binary modules, to find out directory names ...
 
     ObjectFileLoader loadedObjectHandles do:[:h |
-        |cls prj mDir|
-
-        cls := h classes firstIfEmpty:nil.
-        cls notNil ifTrue:[
-            prj := packages at:cls package ifAbsent:nil.
-            prj notNil ifTrue:[
-                mDir := h pathName asFilename directory pathName.
-                prj directory = '???' ifTrue:[
-                    prj directory:mDir
-                ] ifFalse:[
-                    prj directory ~= mDir ifTrue:[
-                        ('Project [warning]: conflicting project directories for ' , cls package) infoPrintCR.
-                    ]
-                ]
-            ]
-        ].
+	|cls prj mDir|
+
+	cls := h classes firstIfEmpty:nil.
+	cls notNil ifTrue:[
+	    prj := packages at:cls package ifAbsent:nil.
+	    prj notNil ifTrue:[
+		mDir := h pathName asFilename directory pathName.
+		prj directory = '???' ifTrue:[
+		    prj directory:mDir
+		] ifFalse:[
+		    prj directory ~= mDir ifTrue:[
+			('Project [warning]: conflicting project directories for ' , cls package) infoPrintCR.
+		    ]
+		]
+	    ]
+	].
     ].
 
     self changed:#allProjects
@@ -253,18 +253,18 @@
 
 initialize
     SystemProject isNil ifTrue:[
-        NextSequential := 1.
-        SystemProject := self new name:'default'.
-        SystemProject package:'private'.
-        SystemProject defaultNameSpace:Smalltalk.
-        SystemProject comment:'A default (dummy) project. 
+	NextSequential := 1.
+	SystemProject := self new name:'default'.
+	SystemProject package:'private'.
+	SystemProject defaultNameSpace:Smalltalk.
+	SystemProject comment:'A default (dummy) project. 
 Will be made the current project in case no real project is ever activated.'.
 
-        "
-         the SystemProject does not keep a record if changes,
-         but instead depends on the changes file - recording anything there.
-        "
-        SystemProject changeSet:nil.
+	"
+	 the SystemProject does not keep a record if changes,
+	 but instead depends on the changes file - recording anything there.
+	"
+	SystemProject changeSet:nil.
     ].
 
     CurrentProject := SystemProject.
@@ -291,8 +291,8 @@
 
     allProjects := self knownProjects.
     (allProjects detect:[:p | p package = aProject package] ifNone:nil) notNil ifTrue:[
-        self warn:'Project for ' , aProject package , ' is already present.'.
-        ^ self.
+	self warn:'Project for ' , aProject package , ' is already present.'.
+	^ self.
     ].
 
     AllProjects add:aProject.
@@ -323,7 +323,7 @@
 
 currentPackageName
     CurrentProject notNil ifTrue:[
-        ^ CurrentProject package
+	^ CurrentProject package
     ].
     ^ nil
 
@@ -340,7 +340,7 @@
 
 knownProjects
     AllProjects isNil ifTrue:[
-        self initKnownProjects
+	self initKnownProjects
     ].
     ^ AllProjects ? #()
 !
@@ -483,7 +483,7 @@
     p := CurrentProject.
     (p notNil 
     and:[(c := p changeSet) notNil]) ifTrue:[
-        c addRemoveSelectorChange:aSelector in:aClass 
+	c addRemoveSelectorChange:aSelector in:aClass 
     ]
 
     "Created: / 16.2.1998 / 12:45:10 / cg"
@@ -498,9 +498,9 @@
 
     p := CurrentProject.
     p notNil ifTrue:[
-        dirName := p directory  
+	dirName := p directory  
     ] ifFalse:[
-        dirName := Filename currentDirectory name
+	dirName := Filename currentDirectory name
     ].
     ^ dirName
 
@@ -517,7 +517,7 @@
     p := CurrentProject.
     (p notNil 
     and:[p ~~ SystemProject]) ifTrue:[
-        p rememberOverwrittenMethod:newMethod from:oldMethod
+	p rememberOverwrittenMethod:newMethod from:oldMethod
     ] ifFalse:[
 "/        'Project [info]: DefaultProject does not remember overwritten methods' infoPrintCR
     ]
@@ -531,7 +531,7 @@
     "add a subproject - obsolete; we use prerequisites now"
 
     subProjects isNil ifTrue:[
-        subProjects := OrderedCollection new.
+	subProjects := OrderedCollection new.
     ].
     subProjects add:aProject
 !
@@ -573,11 +573,11 @@
 
     prevDefault := self defaultNameSpace.
     aNamespace ~~ prevDefault ifTrue:[
-        self propertyAt:#defaultNameSpace put:aNamespace.
-        self changed:#defaultNameSpace.
-        self == CurrentProject ifTrue:[
-            Project changed:#defaultNameSpace 
-        ]
+	self propertyAt:#defaultNameSpace put:aNamespace.
+	self changed:#defaultNameSpace.
+	self == CurrentProject ifTrue:[
+	    Project changed:#defaultNameSpace 
+	]
     ]
 
     "Created: 2.1.1997 / 19:54:37 / cg"
@@ -601,7 +601,7 @@
     directoryName := aDirectoryName.
     self changed:#directory.
     self == CurrentProject ifTrue:[
-        Project changed:#directory 
+	Project changed:#directory 
     ]
 
     "Modified: 27.1.1997 / 12:00:47 / cg"
@@ -639,7 +639,7 @@
     name := aString.
     self changed:#name.
     self == CurrentProject ifTrue:[
-        Project changed:#name
+	Project changed:#name
     ]
 
     "Modified: 27.1.1997 / 12:01:09 / cg"
@@ -800,17 +800,17 @@
     "remove the all of my classes & patches from the system"
 
     self classInfo do:[:clsInfo |
-        |clsName cls|
-
-        clsName := clsInfo className.
-        clsName isSymbol ifTrue:[
-            cls := Smalltalk at:clsName.
-            cls notNil ifTrue:[
-                cls removeFromSystem.
-            ].
-        ] ifFalse:[
-            self halt
-        ].
+	|clsName cls|
+
+	clsName := clsInfo className.
+	clsName isSymbol ifTrue:[
+	    cls := Smalltalk at:clsName.
+	    cls notNil ifTrue:[
+		cls removeFromSystem.
+	    ].
+	] ifFalse:[
+	    self halt
+	].
     ].
 
 !
@@ -831,7 +831,7 @@
      Allows previous methods to be reconstructed."
 
     overwrittenMethods isNil ifTrue:[
-        overwrittenMethods := IdentityDictionary new.
+	overwrittenMethods := IdentityDictionary new.
     ].
     overwrittenMethods at:newMethod put:oldMethod
 
@@ -855,7 +855,7 @@
     "/ for tiny-configurations, allow ChangeSet to be absent
     "/
     ChangeSet notNil ifTrue:[
-        changeSet := ChangeSet new.
+	changeSet := ChangeSet new.
     ].
     self directory:'.'.
     self repositoryModule:(OperatingSystem getLoginName).
@@ -881,16 +881,16 @@
     cond == #never ifTrue:[^ false].
 
     cond == #unix ifTrue:[
-        ^ OperatingSystem isUNIXlike
+	^ OperatingSystem isUNIXlike
     ].
     cond == #win32 ifTrue:[
-        ^ OperatingSystem isMSWINDOWSlike
+	^ OperatingSystem isMSWINDOWSlike
     ].
     cond == #vms ifTrue:[
-        ^ OperatingSystem isVMSlike
+	^ OperatingSystem isVMSlike
     ].
     cond == #macos ifTrue:[
-        ^ OperatingSystem isMAClike
+	^ OperatingSystem isMAClike
     ].
     self halt:'bad condition'
 !
@@ -909,42 +909,42 @@
     "/ this will fix things (i.e. nil superclasses ...)
 
     2 timesRepeat:[
-        self classInfo do:[:clsInfo |
-            |clsName clsFileNameString cls clsFilename 
-             cond include asAutoload|
-
-            clsName := clsInfo className.
-            clsFileNameString := clsInfo classFileName.
-            clsFileNameString isNil ifTrue:[clsFileNameString := clsName , '.st'].
-
-            clsName isSymbol ifTrue:[
-                clsFilename := myDirectory construct:clsFileNameString.
-                cls := Smalltalk at:clsName.
-                (cls isNil or:[firstTrip]) ifTrue:[
-                    "/ ok - really not yet loaded.
-                    Transcript showCR:'loading ' , clsFilename pathName , ' ...'.
-                ] ifFalse:[
-                    Transcript showCR:'reloading ' , clsFilename pathName , ' ...'.
-                ].
-                "/ check condition ...
-                cond := clsInfo conditionForInclusion.
-                (self conditionForInclusionIsTrue:cond) ifTrue:[
-                    (self conditionForAutoloadIsTrue:cond) ifTrue:[
-                        Smalltalk
-                            installAutoloadedClassNamed:clsName
-                            category:'autoloaded'
-                            package:self package    
-                            revision:nil
-                    ] ifFalse:[
-                        Smalltalk fileIn:clsFilename
-                    ]
-                ]
-            ] ifFalse:[
-                self halt
-            ].
-        ].
-
-        firstTrip := false.
+	self classInfo do:[:clsInfo |
+	    |clsName clsFileNameString cls clsFilename 
+	     cond include asAutoload|
+
+	    clsName := clsInfo className.
+	    clsFileNameString := clsInfo classFileName.
+	    clsFileNameString isNil ifTrue:[clsFileNameString := clsName , '.st'].
+
+	    clsName isSymbol ifTrue:[
+		clsFilename := myDirectory construct:clsFileNameString.
+		cls := Smalltalk at:clsName.
+		(cls isNil or:[firstTrip]) ifTrue:[
+		    "/ ok - really not yet loaded.
+		    Transcript showCR:'loading ' , clsFilename pathName , ' ...'.
+		] ifFalse:[
+		    Transcript showCR:'reloading ' , clsFilename pathName , ' ...'.
+		].
+		"/ check condition ...
+		cond := clsInfo conditionForInclusion.
+		(self conditionForInclusionIsTrue:cond) ifTrue:[
+		    (self conditionForAutoloadIsTrue:cond) ifTrue:[
+			Smalltalk
+			    installAutoloadedClassNamed:clsName
+			    category:'autoloaded'
+			    package:self package    
+			    revision:nil
+		    ] ifFalse:[
+			Smalltalk fileIn:clsFilename
+		    ]
+		]
+	    ] ifFalse:[
+		self halt
+	    ].
+	].
+
+	firstTrip := false.
     ].
 
 !
@@ -968,8 +968,8 @@
 
     module := pack at:'repository.module' ifAbsent:nil.
     module notNil ifTrue:[
-        repositoryModule := module.
-        repositoryDirectory := pack at:'repository.directory' ifAbsent:''.
+	repositoryModule := module.
+	repositoryDirectory := pack at:'repository.directory' ifAbsent:''.
     ].
 
     prerequisites := pack at:'prerequisites' ifAbsent:#().
@@ -977,41 +977,41 @@
 
     s := pack at:'nameSpace' ifAbsent:nil.
     s notNil ifTrue:[
-        self defaultNameSpace:(Namespace name:s asSymbol).
+	self defaultNameSpace:(Namespace name:s asSymbol).
     ].
 
     subProjects := pack at:'subProjects' ifAbsent:subProjects.
     (s := pack at:'comment' ifAbsent:nil) notNil ifTrue:[
-        self comment:s
+	self comment:s
     ].
 
     "/ first, all of the conditions ...
     targetConditions := Dictionary new.
     pack keysAndValuesDo:[:key :val |
-        |conditionKey|
-
-        (key startsWith:'target.condition.') ifTrue:[
-            conditionKey := key copyFrom:'target.condition.' size + 1.
-            targetConditions at:conditionKey put:val.
-        ]
+	|conditionKey|
+
+	(key startsWith:'target.condition.') ifTrue:[
+	    conditionKey := key copyFrom:'target.condition.' size + 1.
+	    targetConditions at:conditionKey put:val.
+	]
     ].
 
     properties isNil ifTrue:[
-        properties := IdentityDictionary new
+	properties := IdentityDictionary new
     ].
     properties at:#'targetconditions' put:targetConditions.
 
     sourcesSubDir := pack at:'sources' ifAbsent:nil.
     sourcesSubDir notNil ifTrue:[
-        properties at:#'sourcesDirectory' put:sourcesSubDir.
+	properties at:#'sourcesDirectory' put:sourcesSubDir.
     ].
     methodsFile := pack at:'methodsFile' ifAbsent:nil.
     methodsFile size > 0 ifTrue:[
-        properties at:#'methodsFile' put:methodsFile.
+	properties at:#'methodsFile' put:methodsFile.
     ].
     files := pack at:'files' ifAbsent:nil.
     files notNil ifTrue:[
-        properties at:#'files' put:files.
+	properties at:#'files' put:files.
     ].
 
     "/ fetch class info
@@ -1021,53 +1021,53 @@
     "/    condition (optional)  - #unix / #win32 / #vms / #macos / #always / #never / #autoload
     "/    fileName (optional)
     (pack at:'classes' default:#()) do:[:info |
-        |condKey className optionalFileName|
-
-        condKey := #always.
-        info isSymbol ifTrue:[
-            className := info.
-        ] ifFalse:[
-            className := info at:1.
-            info size > 1 ifTrue:[
-                condKey := info at:2.
-                info size > 2 ifTrue:[
-                    optionalFileName := info at:3.
-                ]
-            ].
-        ].
-        self 
-            addClass:className 
-            conditionForInclusion:condKey 
-            classFileName:optionalFileName
+	|condKey className optionalFileName|
+
+	condKey := #always.
+	info isSymbol ifTrue:[
+	    className := info.
+	] ifFalse:[
+	    className := info at:1.
+	    info size > 1 ifTrue:[
+		condKey := info at:2.
+		info size > 2 ifTrue:[
+		    optionalFileName := info at:3.
+		]
+	    ].
+	].
+	self 
+	    addClass:className 
+	    conditionForInclusion:condKey 
+	    classFileName:optionalFileName
     ].
 
     "/ fetch methods info
 
     (pack at:'methods' default:#()) do:[:info |
-        |condKey className methodName optionalFileName|
-
-        condKey := #always.
-        className := info at:1.
-        methodName := info at:2.
-        info size > 2 ifTrue:[
-            optionalFileName := info at:3.
-            info size > 3 ifTrue:[
-                condKey := info at:4.
-            ]
-        ].
-        self 
-            addMethod:methodName inClass:className 
-            conditionForInclusion:condKey 
-            fileName:optionalFileName
+	|condKey className methodName optionalFileName|
+
+	condKey := #always.
+	className := info at:1.
+	methodName := info at:2.
+	info size > 2 ifTrue:[
+	    optionalFileName := info at:3.
+	    info size > 3 ifTrue:[
+		condKey := info at:4.
+	    ]
+	].
+	self 
+	    addMethod:methodName inClass:className 
+	    conditionForInclusion:condKey 
+	    fileName:optionalFileName
     ].
 
     self wasLoadedFromFile:true.
 
     "/ all remaining properties
     pack keysAndValuesDo:[:key :val |
-        (key startsWith:'property.') ifTrue:[
-            self propertyAt:(key copyFrom:'property.' size+1) asSymbol put:val.
-        ]
+	(key startsWith:'property.') ifTrue:[
+	    self propertyAt:(key copyFrom:'property.' size+1) asSymbol put:val.
+	]
     ].
 
     "
@@ -1093,7 +1093,7 @@
     fn := fn withSuffix:'prj'.
 
     fn exists ifTrue:[
-        fn copyTo:(fn pathName , '.bak')
+	fn copyTo:(fn pathName , '.bak')
     ].
     s := fn writeStream.
     self saveAsProjectFileOn:s.
@@ -1145,8 +1145,8 @@
 
     defNS := self defaultNameSpace.
     (defNS ~~ Smalltalk) ifTrue:[
-        s nextPutAll:'nameSpace'. 
-        s tab. s nextPutLine:(defNS name storeString).
+	s nextPutAll:'nameSpace'. 
+	s tab. s nextPutLine:(defNS name storeString).
     ].
 
     s nextPutAll:'
@@ -1161,44 +1161,44 @@
     s cr.
 
     (t := properties at:#'sourcesDirectory' ifAbsent:nil) notNil ifTrue:[
-        s nextPutAll:'sources'. 
-        s tab. s nextPutLine:(t storeString).
+	s nextPutAll:'sources'. 
+	s tab. s nextPutLine:(t storeString).
     ].
 
     first := true.
     properties keysAndValuesDo:[:key :val |
-        (#(
-            comment
-            wasLoadedFromFile
-            targetconditions
-            classes
-            classInfo
-            methodInfo
-            prerequisiteClasses
-            files
-            sourcesDirectory
-            methodsFile
-            type
-            defaultNameSpace
-        ) includes:key) ifFalse:[
-            first ifTrue:[
-                first := false.
-                s nextPutAll:'
+	(#(
+	    comment
+	    wasLoadedFromFile
+	    targetconditions
+	    classes
+	    classInfo
+	    methodInfo
+	    prerequisiteClasses
+	    files
+	    sourcesDirectory
+	    methodsFile
+	    type
+	    defaultNameSpace
+	) includes:key) ifFalse:[
+	    first ifTrue:[
+		first := false.
+		s nextPutAll:'
 ;
 ; properties:
 ;
 '.
-            ].    
-            s nextPutAll:'property.'; nextPutAll:key. 
-            s tab. 
-            key == #defaultNameSpace ifTrue:[
-                s nextPutLine:val name storeString.
-            ] ifFalse:[
-                s nextPutLine:val storeString.
-            ]
-        ]
+	    ].    
+	    s nextPutAll:'property.'; nextPutAll:key. 
+	    s tab. 
+	    key == #defaultNameSpace ifTrue:[
+		s nextPutLine:val name storeString.
+	    ] ifFalse:[
+		s nextPutLine:val storeString.
+	    ]
+	]
     ].
-        
+	
 "/    coll := self subProjects.
 "/    coll size > 0 ifTrue:[
 "/        s nextPutLine:'[subprojects]'. 
@@ -1215,33 +1215,33 @@
     s nextPutAll:'prerequisites'; tab.
     coll := self prerequisites.
     coll size = 0 ifTrue:[
-        s nextPutLine:'#()'. 
+	s nextPutLine:'#()'. 
     ] ifFalse:[    
-        s nextPutLine:'#( \'. 
-        coll do:[:aProjectOrProjectNameList |
-            |pName pPath|
-
-            aProjectOrProjectNameList isString ifTrue:[
-                pName := aProjectOrProjectNameList.
-            ] ifFalse:[
-                aProjectOrProjectNameList isArray ifTrue:[
-                    pName := aProjectOrProjectNameList at:1.
-                    pPath := aProjectOrProjectNameList at:2.
-                ] ifFalse:[
-                    pName := aProjectOrProjectNameList name.
-                    pPath := aProjectOrProjectNameList repositoryPath.    
-                ]
-            ].
-
-            pPath isNil ifTrue:[
-                s tab. s nextPutAll:(pName storeString); nextPutLine:' \'.
-            ] ifFalse:[
-                s tab. s nextPutAll:'( '.
-                s nextPutAll:(pName storeString); space;
-                  nextPutAll:(pPath storeString); nextPutLine:') \'.
-            ]
-        ].
-        s nextPutLine:')'.
+	s nextPutLine:'#( \'. 
+	coll do:[:aProjectOrProjectNameList |
+	    |pName pPath|
+
+	    aProjectOrProjectNameList isString ifTrue:[
+		pName := aProjectOrProjectNameList.
+	    ] ifFalse:[
+		aProjectOrProjectNameList isArray ifTrue:[
+		    pName := aProjectOrProjectNameList at:1.
+		    pPath := aProjectOrProjectNameList at:2.
+		] ifFalse:[
+		    pName := aProjectOrProjectNameList name.
+		    pPath := aProjectOrProjectNameList repositoryPath.    
+		]
+	    ].
+
+	    pPath isNil ifTrue:[
+		s tab. s nextPutAll:(pName storeString); nextPutLine:' \'.
+	    ] ifFalse:[
+		s tab. s nextPutAll:'( '.
+		s nextPutAll:(pName storeString); space;
+		  nextPutAll:(pPath storeString); nextPutLine:') \'.
+	    ]
+	].
+	s nextPutLine:')'.
     ].
 
     s nextPutAll:'
@@ -1252,17 +1252,17 @@
     s nextPutAll:'prerequisiteClasses'; tab.
     coll := self prerequisiteClasses.
     coll size = 0 ifTrue:[
-        s nextPutLine:'#()'. 
+	s nextPutLine:'#()'. 
     ] ifFalse:[    
-        s nextPutLine:'#( \'. 
-        coll do:[:aClassOrSymbol | |className|
-
-            (className := aClassOrSymbol) isSymbol ifFalse:[
-                className := aClassOrSymbol name
-            ].
-            s tab. s nextPutAll:(className storeString); nextPutLine:' \'.
-        ].
-        s nextPutLine:')'.
+	s nextPutLine:'#( \'. 
+	coll do:[:aClassOrSymbol | |className|
+
+	    (className := aClassOrSymbol) isSymbol ifFalse:[
+		className := aClassOrSymbol name
+	    ].
+	    s tab. s nextPutAll:(className storeString); nextPutLine:' \'.
+	].
+	s nextPutLine:')'.
     ].
 
     s nextPutAll:'
@@ -1277,38 +1277,38 @@
 
     coll := self classInfo.
     coll size = 0 ifTrue:[
-        s nextPutLine:'#()'. 
+	s nextPutLine:'#()'. 
     ] ifFalse:[    
-        s nextPutLine:'#( \'.
-        "/ find the longest className (for layout only)
-        
-        maxLen := coll inject:0 into:[:maxSoFar :aClassInfo |
-                                        |clsName|
-
-                                        clsName := aClassInfo className.
-                                        maxSoFar max:clsName storeString size
-                                     ].
-
-        coll do:[:aClassInfo |
-            |clsName fileName cond|
-
-            clsName := aClassInfo className.
-            fileName := aClassInfo classFileName.
-            fileName = (clsName , '.st') ifTrue:[
-                fileName := nil
-            ].
-            cond := (aClassInfo conditionForInclusion) ? #always.
-            s tab. s nextPutAll:'( '; 
-                     nextPutAll:(clsName storeString paddedTo:maxLen).
-            (cond ~~ #always or:[fileName notNil]) ifTrue:[
-                s tab; nextPutAll:cond storeString.
-            ].
-            fileName notNil ifTrue:[
-                s tab; nextPutAll:fileName storeString.
-            ].
-            s nextPutLine:') \'.
-        ].
-        s nextPutLine:')'.
+	s nextPutLine:'#( \'.
+	"/ find the longest className (for layout only)
+	
+	maxLen := coll inject:0 into:[:maxSoFar :aClassInfo |
+					|clsName|
+
+					clsName := aClassInfo className.
+					maxSoFar max:clsName storeString size
+				     ].
+
+	coll do:[:aClassInfo |
+	    |clsName fileName cond|
+
+	    clsName := aClassInfo className.
+	    fileName := aClassInfo classFileName.
+	    fileName = (clsName , '.st') ifTrue:[
+		fileName := nil
+	    ].
+	    cond := (aClassInfo conditionForInclusion) ? #always.
+	    s tab. s nextPutAll:'( '; 
+		     nextPutAll:(clsName storeString paddedTo:maxLen).
+	    (cond ~~ #always or:[fileName notNil]) ifTrue:[
+		s tab; nextPutAll:cond storeString.
+	    ].
+	    fileName notNil ifTrue:[
+		s tab; nextPutAll:fileName storeString.
+	    ].
+	    s nextPutLine:') \'.
+	].
+	s nextPutLine:')'.
     ].
 
     s nextPutAll:'
@@ -1323,36 +1323,36 @@
 
     coll := self methodInfo.
     coll size = 0 ifTrue:[
-        s nextPutLine:'#()'. 
+	s nextPutLine:'#()'. 
     ] ifFalse:[    
-        s nextPutLine:'#( \'.
-        "/ find the longest className (for layout only)
-
-        maxLen := coll inject:0 into:[:maxSoFar :aMethodInfo |
-                                        |clsName|
-
-                                        clsName := aMethodInfo className.
-                                        maxSoFar max:clsName storeString size
-                                     ].
-
-        coll do:[:aMethodInfo |
-            |clsName mthdName fileName cond|
-
-            clsName := aMethodInfo className.
-            mthdName := aMethodInfo methodName.
-            s tab. s nextPutAll:'( '; 
-                     nextPutAll:(clsName storeString paddedTo:maxLen); 
-                     tab; nextPutAll:mthdName storeString.
-            s nextPutLine:') \'.
-        ].
-        s nextPutLine:')'.
+	s nextPutLine:'#( \'.
+	"/ find the longest className (for layout only)
+
+	maxLen := coll inject:0 into:[:maxSoFar :aMethodInfo |
+					|clsName|
+
+					clsName := aMethodInfo className.
+					maxSoFar max:clsName storeString size
+				     ].
+
+	coll do:[:aMethodInfo |
+	    |clsName mthdName fileName cond|
+
+	    clsName := aMethodInfo className.
+	    mthdName := aMethodInfo methodName.
+	    s tab. s nextPutAll:'( '; 
+		     nextPutAll:(clsName storeString paddedTo:maxLen); 
+		     tab; nextPutAll:mthdName storeString.
+	    s nextPutLine:') \'.
+	].
+	s nextPutLine:')'.
     ].
 
     methodsFile := properties at:#methodsFile ifAbsent:nil.
     methodsFile size > 0 ifTrue:[
-        s cr; nextPutLine:';'; nextPutLine:'; methods above are stored in:'; nextPutLine:';'.
-        s nextPutLine:';'.
-        s nextPutAll:'methodsFile'; tab; nextPutLine:'''' , methodsFile , ''''.
+	s cr; nextPutLine:';'; nextPutLine:'; methods above are stored in:'; nextPutLine:';'.
+	s nextPutLine:';'.
+	s nextPutAll:'methodsFile'; tab; nextPutLine:'''' , methodsFile , ''''.
     ].
 
     s nextPutAll:'
@@ -1364,13 +1364,13 @@
     s nextPutAll:'files'; tab.
     coll := properties at:#'files' ifAbsent:#().
     coll size = 0 ifTrue:[
-        s nextPutLine:'#()'. 
+	s nextPutLine:'#()'. 
     ] ifFalse:[    
-        s nextPutLine:'#( \'. 
-        coll do:[:aFileEntry |
-            s tab. s nextPutAll:(aFileEntry storeString); nextPutLine:' \'.
-        ].
-        s nextPutLine:')'.
+	s nextPutLine:'#( \'. 
+	coll do:[:aFileEntry |
+	    s tab. s nextPutAll:(aFileEntry storeString); nextPutLine:' \'.
+	].
+	s nextPutLine:')'.
     ].
 
     "
@@ -1401,34 +1401,34 @@
     firstBad := nil.
 
     classes := classes collect:[:clsOrSymbol |  |cls|
-                                        clsOrSymbol isSymbol ifTrue:[
-                                            cls := Smalltalk at:clsOrSymbol.
-                                            cls isNil ifTrue:[
-                                                numBad := numBad + 1.
-                                                firstBad := firstBad ? clsOrSymbol.
-                                            ] ifFalse:[
-                                                cls isLoaded ifFalse:[
-                                                    cls autoLoad.
-                                                    cls isLoaded ifFalse:[
-                                                        cls := nil
-                                                    ]
-                                                ].
-                                            ].
-                                            cls.
-                                        ] ifFalse:[
-                                            clsOrSymbol
-                                        ]
-                              ].
+					clsOrSymbol isSymbol ifTrue:[
+					    cls := Smalltalk at:clsOrSymbol.
+					    cls isNil ifTrue:[
+						numBad := numBad + 1.
+						firstBad := firstBad ? clsOrSymbol.
+					    ] ifFalse:[
+						cls isLoaded ifFalse:[
+						    cls autoLoad.
+						    cls isLoaded ifFalse:[
+							cls := nil
+						    ]
+						].
+					    ].
+					    cls.
+					] ifFalse:[
+					    clsOrSymbol
+					]
+			      ].
 
     numBad ~~ 0 ifTrue:[
-        msg := 'Cannot generate ''loadAll''-file.\\'.
-        msg := msg , 'Reason: Class ''' , firstBad asText allBold
-                   , ''' is not loaded.'.
-        numBad ~~ 1 ifTrue:[
-            msg := msg , '\(' , (numBad-1) printString , ' more unloaded classes were found)'
-        ].
-        self warn:msg withCRs.
-        ^ self.
+	msg := 'Cannot generate ''loadAll''-file.\\'.
+	msg := msg , 'Reason: Class ''' , firstBad asText allBold
+		   , ''' is not loaded.'.
+	numBad ~~ 1 ifTrue:[
+	    msg := msg , '\(' , (numBad-1) printString , ' more unloaded classes were found)'
+	].
+	self warn:msg withCRs.
+	^ self.
     ].
 
     "/ to not list private classes
@@ -1440,20 +1440,21 @@
     d := directoryName asFilename.
     f := d construct:'loadAll'.
     f exists ifTrue:[
-        f renameTo:(d construct:'loadAll.bak')
+	f renameTo:(d construct:'loadAll.bak')
     ].
     out := f writeStream.
     out isNil ifTrue:[
-        self warn:'cannot create loadAll'.
-        (d construct:'loadAll.bak') renameTo:f.
-        ^ self
+	self warn:'cannot create loadAll'.
+	(d construct:'loadAll.bak') renameTo:f.
+	^ self
     ].
 
+    out nextPutLine:'"/
+"/ $' , 'Header' , '$'.
+    out nextPutLine:'"/
+"/ loadAll-file to fileIn code for: ' , self package.
+    
     out nextPutAll:'"/
-"/ $' , 'Header' , '$
-"/
-"/ loadAll-file to fileIn code for: ' , self package , '
-"/
 "/ Automatically generated from project definition.
 "/ DO NOT MODIFY THIS fILE;
 "/ modify the .prj file instead, and regenerate this file
@@ -1462,36 +1463,34 @@
 
 "/
 "/ Prerequisites:
-"/
-'.
+"/'.
     prerequisitePackages := self prerequisitePackages 
-                                collect:[:entry |
-                                    |pName|
-
-                                    entry isString ifTrue:[
-                                        pName := entry
-                                    ] ifFalse:[
-                                        entry isArray ifTrue:[
-                                            pName := entry at:1
-                                        ] ifFalse:[
-                                            pName := entry name
-                                        ]
-                                    ]
-                                ].
+				collect:[:entry |
+				    |pName|
+
+				    entry isString ifTrue:[
+					pName := entry
+				    ] ifFalse:[
+					entry isArray ifTrue:[
+					    pName := entry at:1
+					] ifFalse:[
+					    pName := entry name
+					]
+				    ]
+				].
 
     prerequisitePackages size == 0 ifTrue:[
-    out nextPutAll:'
-"/ Smalltalk loadPackage:''module:directory''.
-"/ Smalltalk loadPackage:''....''.
-'   ] ifFalse:[
-        out cr.
-        prerequisitePackages do:[:packName |
-            out nextPutLine:'Smalltalk loadPackage:''' , packName , '''.'.
-        ]
+	out nextPutLine:''.
+	out nextPutLine:'"/ Smalltalk loadPackage:''module:directory''.'.
+	out nextPutLine:'"/ Smalltalk loadPackage:''....''.'.
+    ] ifFalse:[
+	out cr.
+	prerequisitePackages do:[:packName |
+	    out nextPutLine:'Smalltalk loadPackage:''' , packName , '''.'.
+	]
     ].
 
-    out nextPutAll:
-'!!
+    out nextPutAll:'!!
 
 "{ package:''' , self package , ''' }"!!
 
@@ -1500,25 +1499,27 @@
 ''loading package ' , self package , ' ...'' infoPrintCR.
 
 files := #(
+.
 '.
 
     classes do:[:cls |
-        |clsInfo cond|
-
-        clsInfo := self classInfoFor:cls.
-        cond := clsInfo conditionForInclusion.
-        (cond == #always or:[cond == #autoload]) ifTrue:[
-            out nextPutAll:'  '''.
-            cls nameWithoutNameSpacePrefix printOn:out.
-            out nextPutAll:'.st'''.
-            out cr.
-        ]
+	|clsInfo cond|
+
+	clsInfo := self classInfoFor:cls.
+	cond := clsInfo conditionForInclusion.
+	(cond == #always or:[cond == #autoload]) ifTrue:[
+	    out nextPutAll:'  '''.
+	    cls nameWithoutNameSpacePrefix printOn:out.
+	    out nextPutAll:'.st'''.
+	    out cr.
+	]
     ].
     (methodsFile := self propertyAt:#methodsFile) size > 0 ifTrue:[
-         out 
-            nextPutAll:'  ''';
-            nextPutAll:methodsFile;
-            nextPutAll:''''.
+	 out 
+	    nextPutAll:'  ''';
+	    nextPutAll:methodsFile;
+	    nextPutAll:'''';
+	    cr.
     ].
 
     out nextPutAll:') asOrderedCollection.
@@ -1527,19 +1528,18 @@
     |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 classFilename]].
+	loaded := Set new:(handle classes size).
+	handle classes do:[:c| c isMeta ifFalse:[loaded add:c classFilename]].
 '.
+    
     methodsFile size > 0 ifTrue:[
-        out nextPutAll:
-'        loaded add:''' , methodsFile , '''.'.
+	out nextPutLine:('        loaded add:''' , methodsFile , '''.').
     ].
-    out nextPutAll:'
-        files := files asOrderedCollection select:[:f| (loaded includes:f) not].
+    out nextPutAll:'        files := files asOrderedCollection select:[:f| (loaded includes:f) not].
     ].
-]. 
+].
 
 files do:[:s |
     ''.'' infoPrint.
@@ -1547,7 +1547,7 @@
 ].
 '' '' infoPrintCR.
 '' done (' , self package , ').'' infoPrintCR.
-'.
+.'.
 
     out close
 !
@@ -1564,9 +1564,9 @@
     top := (d , '/' , (self findTopFrom:directoryName)) asFilename pathName.
 
     (OperatingSystem 
-        executeCommand:('sh ' , top , '/rules/stmkmf')
-        inDirectory:d) ifFalse:[
-        self warn:'Could not execute stmkmf - no Makefile built.'
+	executeCommand:('sh ' , top , '/rules/stmkmf')
+	inDirectory:d) ifFalse:[
+	self warn:'Could not execute stmkmf - no Makefile built.'
     ].
 
 !
@@ -1575,15 +1575,15 @@
     "actually, creates all files to do a make in the project directory"
 
     directoryName asFilename exists ifFalse:[
-        (self confirm:'create new projectDirectory: ' , directoryName) 
-            ifFalse:[^ self].
-        OperatingSystem recursiveCreateDirectory:directoryName.
+	(self confirm:'create new projectDirectory: ' , directoryName) 
+	    ifFalse:[^ self].
+	OperatingSystem recursiveCreateDirectory:directoryName.
     ].
     self createMakefile.
     self createSourcefiles.
     self createProtoMakefile.
     (self propertyAt:#deliverLoadAllFile) == true ifTrue:[
-        self createLoadAllFile
+	self createLoadAllFile
     ].
 !
 
@@ -1598,33 +1598,33 @@
     firstBad := nil.
 
     classes := classes collect:[:clsOrSymbol |  |cls|
-                                        clsOrSymbol isSymbol ifTrue:[
-                                            cls := Smalltalk at:clsOrSymbol.
-                                            cls isNil ifTrue:[
-                                                numBad := numBad + 1.
-                                                firstBad := firstBad ? clsOrSymbol.
-                                            ] ifFalse:[
-                                                cls isLoaded ifFalse:[
-                                                    cls autoLoad.
-                                                    cls isLoaded ifFalse:[
-                                                        cls := nil
-                                                    ]
-                                                ].
-                                            ].
-                                            cls.
-                                        ] ifFalse:[
-                                            clsOrSymbol
-                                        ]
-                              ].
+					clsOrSymbol isSymbol ifTrue:[
+					    cls := Smalltalk at:clsOrSymbol.
+					    cls isNil ifTrue:[
+						numBad := numBad + 1.
+						firstBad := firstBad ? clsOrSymbol.
+					    ] ifFalse:[
+						cls isLoaded ifFalse:[
+						    cls autoLoad.
+						    cls isLoaded ifFalse:[
+							cls := nil
+						    ]
+						].
+					    ].
+					    cls.
+					] ifFalse:[
+					    clsOrSymbol
+					]
+			      ].
     numBad ~~ 0 ifTrue:[
-        msg := 'Cannot generate ''Make.proto''-file.\\'.
-        msg := msg , 'Reason: Class ''' , firstBad asText allBold
-                   , ''' is not loaded.'.
-        numBad ~~ 1 ifTrue:[
-            msg := msg , '\(' , (numBad-1) printString , ' more unloaded classes were found)'
-        ].
-        self warn:msg withCRs.
-        ^ self.
+	msg := 'Cannot generate ''Make.proto''-file.\\'.
+	msg := msg , 'Reason: Class ''' , firstBad asText allBold
+		   , ''' is not loaded.'.
+	numBad ~~ 1 ifTrue:[
+	    msg := msg , '\(' , (numBad-1) printString , ' more unloaded classes were found)'
+	].
+	self warn:msg withCRs.
+	^ self.
     ].
 
     "/ to not list private classes
@@ -1639,16 +1639,19 @@
     d := directoryName asFilename.
     f := d construct:'Make.proto'.
     f exists ifTrue:[
-        f renameTo:(d construct:'Make.proto.bak')
+	f renameTo:(d construct:'Make.proto.bak')
     ].
     s := f writeStream.
     s isNil ifTrue:[
-        self warn:'cannot create prototype Makefile'.
-        ^ self
+	self warn:'cannot create prototype Makefile'.
+	^ self
     ].
-    s nextPutAll:'# $' , 'Header' , '$
-#
-# -- Make.proto created from project at ' , Smalltalk timeStamp , '
+    s nextPutAll:'# $' , 'Header'. 
+    s nextPutLine:'$'.
+    s nextPutAll:'#
+# -- Make.proto created from project at ' . 
+    s nextPutAll:Smalltalk timeStamp. 
+    s nextPutAll:'
 #
 # Warning: YOU SHOULD NOT MODIFY THIS FILE - MODIFY THE .prj FILE INSTEAD
 # and let the ProjectBrowser recreate this file.
@@ -1730,13 +1733,13 @@
 # STCWARNINGS=-warnNonStandard
 # STCWARNINGS=-warnEOLComments
 STCWARNINGS='.
-        (self propertyAt:#'make.stc.warnEOLComments') == false ifTrue:[
-            s nextPutAll:'-warnEOLComments '.
-        ].
-        (self propertyAt:#'make.stc.warnNonStandard') == false ifTrue:[
-            s nextPutAll:'-warnNonStandard '.
-        ].
-        s nextPutAll:((self propertyAt:#'make.stc.WARNINGOPTIONS') ? '') , '
+	(self propertyAt:#'make.stc.warnEOLComments') == false ifTrue:[
+	    s nextPutAll:'-warnEOLComments '.
+	].
+	(self propertyAt:#'make.stc.warnNonStandard') == false ifTrue:[
+	    s nextPutAll:'-warnNonStandard '.
+	].
+	s nextPutAll:((self propertyAt:#'make.stc.WARNINGOPTIONS') ? '') , '
 
 # if your embedded C code requires any system includes, 
 # add the path(es) here:, 
@@ -1804,31 +1807,31 @@
     s nextPutAll:'OBJS='.
 
     classes do:[:aClass |
-        |abbrev clsInfo cond include|
-
-        clsInfo := self classInfoFor:aClass.
-        include := true.
-        clsInfo notNil ifTrue:[
-            cond := clsInfo conditionForInclusion.
-            (self conditionForInclusionIsTrue:cond) ifFalse:[
-                include := false.
-            ] ifTrue:[
-                (self conditionForAutoloadIsTrue:cond) ifTrue:[
-                    include := false
-                ]
-            ].
-        ].
-        include ifTrue:[
-            s nextPutAll:' \'. s cr.
-            abbrev := Smalltalk fileNameForClass:aClass name.
-            s nextPutAll:'  '; nextPutAll:abbrev; nextPutAll:'.$(O)'.
-        ]
+	|abbrev clsInfo cond include|
+
+	clsInfo := self classInfoFor:aClass.
+	include := true.
+	clsInfo notNil ifTrue:[
+	    cond := clsInfo conditionForInclusion.
+	    (self conditionForInclusionIsTrue:cond) ifFalse:[
+		include := false.
+	    ] ifTrue:[
+		(self conditionForAutoloadIsTrue:cond) ifTrue:[
+		    include := false
+		]
+	    ].
+	].
+	include ifTrue:[
+	    s nextPutAll:' \'. s cr.
+	    abbrev := Smalltalk fileNameForClass:aClass name.
+	    s nextPutAll:'  '; nextPutAll:abbrev; nextPutAll:'.$(O)'.
+	]
     ].
     (methodsFile := self propertyAt:#methodsFile) size > 0 ifTrue:[
-         s nextPutAll:' \'. s cr.
-         s nextPutAll:'  '; 
-           nextPutAll:(methodsFile asFilename withoutSuffix baseName);
-           nextPutAll:'.$(O)'.
+	 s nextPutAll:' \'. s cr.
+	 s nextPutAll:'  '; 
+	   nextPutAll:(methodsFile asFilename withoutSuffix baseName);
+	   nextPutAll:'.$(O)'.
     ].
     s cr.
 
@@ -1890,16 +1893,16 @@
     s cr; cr.
 
     type == #executable ifTrue:[
-        s nextPutAll:'all:: $(PROGS)'; cr.
-
-        s nextPutAll:appName.
-        s nextPutAll:':: main.o classList.o $(OBJS)'; cr.
-        s tab;      nextPutAll:'$(LD) $(ST_LDFLAG) $(LDFLAGS) -o ';
-                    nextPutAll:appName;
-                    nextPutAll:' \'; cr.
-        s tab; tab; nextPutAll:'$(CRT0) main.$(O) classList.$(O) $(OBJS) $(EXTRA_OBJ) $(LIBOBJS) \'; cr.
-        s tab; tab; nextPutAll:'$(LIBRUNDIR)/hidata.o $(LIBRUN) \'; cr.
-        s tab; tab; nextPutAll:'$(MATHLIB) $(EXTRALIBS) -lXext $(SYSLIBS) $(OTHERLIBS) $(CRTN)'; cr.
+	s nextPutAll:'all:: $(PROGS)'; cr.
+
+	s nextPutAll:appName.
+	s nextPutAll:':: main.o classList.o $(OBJS)'; cr.
+	s tab;      nextPutAll:'$(LD) $(ST_LDFLAG) $(LDFLAGS) -o ';
+		    nextPutAll:appName;
+		    nextPutAll:' \'; cr.
+	s tab; tab; nextPutAll:'$(CRT0) main.$(O) classList.$(O) $(OBJS) $(EXTRA_OBJ) $(LIBOBJS) \'; cr.
+	s tab; tab; nextPutAll:'$(LIBRUNDIR)/hidata.o $(LIBRUN) \'; cr.
+	s tab; tab; nextPutAll:'$(MATHLIB) $(EXTRALIBS) -lXext $(SYSLIBS) $(OTHERLIBS) $(CRTN)'; cr.
     ].
 
     s close
@@ -1917,58 +1920,58 @@
 
     classes := self classes.
     classes isNil ifTrue:[
-        self warn:'no classes in current project'
+	self warn:'no classes in current project'
     ].
 
     classes notNil ifTrue:[
-        classes do:[:aClass |
-            aClass isLoaded ifFalse:[
-                aClass autoload.
-            ].
-        ].
-        "/ to not list private classes
-        classes := classes select:[:cls | cls owningClass isNil].
-        classes := classes topologicalSort:[:a :b | a isSubclassOf:b].
-
-        classes do:[:aClass |
-            Transcript show:' ... '; showCR:aClass name, '.st'; endEntry.
-            aClass fileOutIn:dir
-        ]
+	classes do:[:aClass |
+	    aClass isLoaded ifFalse:[
+		aClass autoload.
+	    ].
+	].
+	"/ to not list private classes
+	classes := classes select:[:cls | cls owningClass isNil].
+	classes := classes topologicalSort:[:a :b | a isSubclassOf:b].
+
+	classes do:[:aClass |
+	    Transcript show:' ... '; showCR:aClass name, '.st'; endEntry.
+	    aClass fileOutIn:dir
+	]
     ].
 
     methods := self individualMethods.
     methods notNil ifTrue:[
-        methods := methods asIdentitySet.
-        "
-         get classes ...
-        "
-        methodClasses := IdentitySet new.
-        methods do:[:m | 
-                        |mCls|
-
-                        mCls := m containingClass.
-                        mCls isMeta ifTrue:[
-                            mCls := mCls soleInstance.
-                        ].
-                        methodClasses add:mCls].
-        "
-         fileOut by class
-        "
-        methodClasses do:[:cls |
-            stream := (self directory asFilename construct:(cls name , '.chg')) writeStream.
-
-            Transcript show:' ... '; showCR:cls name, '.chg'; endEntry.
-            methods do:[:m |
-                |mCls|
-
-                mCls := m containingClass.
-                (mCls == cls or:[mCls == cls class]) ifTrue:[
-                    mCls fileOutMethod:m on:stream.
-                ].
-                stream cr.
-            ].
-            stream close.
-        ].
+	methods := methods asIdentitySet.
+	"
+	 get classes ...
+	"
+	methodClasses := IdentitySet new.
+	methods do:[:m | 
+			|mCls|
+
+			mCls := m containingClass.
+			mCls isMeta ifTrue:[
+			    mCls := mCls soleInstance.
+			].
+			methodClasses add:mCls].
+	"
+	 fileOut by class
+	"
+	methodClasses do:[:cls |
+	    stream := (self directory asFilename construct:(cls name , '.chg')) writeStream.
+
+	    Transcript show:' ... '; showCR:cls name, '.chg'; endEntry.
+	    methods do:[:m |
+		|mCls|
+
+		mCls := m containingClass.
+		(mCls == cls or:[mCls == cls class]) ifTrue:[
+		    mCls fileOutMethod:m on:stream.
+		].
+		stream cr.
+	    ].
+	    stream close.
+	].
     ].
 
     "Modified: 1.11.1996 / 16:37:15 / cg"
@@ -1985,25 +1988,25 @@
     relParent := '..'.
     foundTop := false.
     [foundTop] whileFalse:[
-        topName := directoryName asFilename construct:relParent.
-        topName isRootDirectory ifTrue:[
-            self warn:'could not find TOP; assume absoulte path to TOP'.
-            ^ nil.
+	topName := directoryName asFilename construct:relParent.
+	topName isRootDirectory ifTrue:[
+	    self warn:'could not find TOP; assume absoulte path to TOP'.
+	    ^ nil.
 "/            topName := '/usr/local/lib/smalltalk'.
 "/            foundTop := true.
-        ] ifFalse:[
-            ((topName construct:'stx') construct:'configurations') exists ifTrue:[
-                ((topName construct:'stx') construct:'include') exists ifTrue:[
-                    ^ relParent , '/stx'.
-                ]
-            ].
-            (topName construct:'configurations') exists ifTrue:[
-                (topName construct:'include') exists ifTrue:[
-                    ^ relParent 
-                ]
-            ].
-            relParent := relParent , '/..'
-        ]
+	] ifFalse:[
+	    ((topName construct:'stx') construct:'configurations') exists ifTrue:[
+		((topName construct:'stx') construct:'include') exists ifTrue:[
+		    ^ relParent , '/stx'.
+		]
+	    ].
+	    (topName construct:'configurations') exists ifTrue:[
+		(topName construct:'include') exists ifTrue:[
+		    ^ relParent 
+		]
+	    ].
+	    relParent := relParent , '/..'
+	]
     ].
     ^ topName pathName
 ! !
@@ -2020,9 +2023,9 @@
     "add a class to the project"
 
     self
-        addClass:classOrClassName 
-        conditionForInclusion:#always 
-        classFileName:fileName
+	addClass:classOrClassName 
+	conditionForInclusion:#always 
+	classFileName:fileName
 
 !
 
@@ -2032,7 +2035,7 @@
     |i clsName|
 
     (clsName := classOrClassName) isBehavior ifTrue:[
-        clsName := classOrClassName name
+	clsName := classOrClassName name
     ].
 
     i := ClassInfo new.
@@ -2048,18 +2051,18 @@
     |infoCollection index nm prefix|
 
     (infoCollection := self classInfo) isNil ifTrue:[
-        self classInfo:(infoCollection := OrderedCollection new).
+	self classInfo:(infoCollection := OrderedCollection new).
     ].
 
     index := infoCollection findFirst:[:i | |nm1 nm2|
-                                        nm1 := i className.
-                                        nm2 := newInfo className.
-                                        nm1 = nm2
-                                      ].
+					nm1 := i className.
+					nm2 := newInfo className.
+					nm1 = nm2
+				      ].
     index ~~ 0 ifTrue:[
-        infoCollection at:index put:newInfo
+	infoCollection at:index put:newInfo
     ] ifFalse:[
-        infoCollection add:newInfo
+	infoCollection add:newInfo
     ]
 !
 
@@ -2094,33 +2097,33 @@
     |infoCollection index nm prefix|
 
     (infoCollection := self methodInfo) isNil ifTrue:[
-        self methodInfo:(infoCollection := OrderedCollection new).
+	self methodInfo:(infoCollection := OrderedCollection new).
     ].
 
     index := infoCollection findFirst:[:i | |cnm1 cnm2|
-                                        cnm1 := i className.
-                                        cnm2 := newInfo className.
-                                        (cnm1 includes:$:) ifFalse:[
-                                            cnm1 := self defaultNameSpace name , '::' , cnm1
-                                        ].
-                                        (cnm2 includes:$:) ifFalse:[
-                                            cnm2 := self defaultNameSpace name , '::' , cnm2
-                                        ].
-                                        cnm1 = cnm2 and:[i methodName = newInfo methodName]
-                                      ].
+					cnm1 := i className.
+					cnm2 := newInfo className.
+					(cnm1 includes:$:) ifFalse:[
+					    cnm1 := self defaultNameSpace name , '::' , cnm1
+					].
+					(cnm2 includes:$:) ifFalse:[
+					    cnm2 := self defaultNameSpace name , '::' , cnm2
+					].
+					cnm1 = cnm2 and:[i methodName = newInfo methodName]
+				      ].
     "/ strip off nameSpace prefix, if its the same as
     "/ the default ...
 
     nm := newInfo className.
     prefix := self defaultNameSpace name , '::'.
     (nm startsWith:prefix) ifTrue:[
-        nm := nm copyFrom:(prefix size + 1).
-        newInfo className:nm asSymbol.
+	nm := nm copyFrom:(prefix size + 1).
+	newInfo className:nm asSymbol.
     ].
     index ~~ 0 ifTrue:[
-        infoCollection at:index put:newInfo
+	infoCollection at:index put:newInfo
     ] ifFalse:[
-        infoCollection add:newInfo
+	infoCollection add:newInfo
     ]
 !
 
@@ -2193,12 +2196,12 @@
     oldValue := self propertyAt:aKey.
 
     properties isNil ifTrue:[
-        properties := IdentityDictionary new
+	properties := IdentityDictionary new
     ].
     properties at:aKey put:aValue.
 
     oldValue ~~ aValue ifTrue:[
-        self changed:aKey.
+	self changed:aKey.
     ].
 
     "Created: / 23.3.1999 / 14:21:11 / cg"
@@ -2212,12 +2215,12 @@
     (infoCollection := self classInfo) isNil ifTrue:[^ self].
 
     (className := classOrClassName) isBehavior ifTrue:[
-        className := classOrClassName name
+	className := classOrClassName name
     ].
 
     index := infoCollection findFirst:[:i | i className = className.].
     index ~~ 0 ifTrue:[
-        infoCollection removeIndex:index
+	infoCollection removeIndex:index
     ]
 !
 
@@ -2234,11 +2237,11 @@
     |sym|
 
     (sym := aSymbol) == #classLibrary ifTrue:[
-        sym := #library
+	sym := #library
     ].
     (#(application library extension smalltalk) includes:sym) ifFalse:[
-        self warn:'invalid project type'.
-        ^ self
+	self warn:'invalid project type'.
+	^ self
     ].
     self propertyAt:#type put:sym
 !
@@ -2270,7 +2273,7 @@
     classes := self classes.
     classes isNil ifTrue:[^ isLoaded ? false].
     classes do:[:aClass |
-        aClass isLoaded ifFalse:[^ false].
+	aClass isLoaded ifFalse:[^ false].
     ].
     ^ true
 
@@ -2282,25 +2285,25 @@
     |classInfo classes|
 
     properties notNil ifTrue:[
-        classInfo := properties at:#classInfo ifAbsent:nil.
-        classInfo notNil ifTrue:[^ classInfo].
+	classInfo := properties at:#classInfo ifAbsent:nil.
+	classInfo notNil ifTrue:[^ classInfo].
     ].
 
     classes := self classes.
     classes size == 0 ifTrue:[
-        classInfo := OrderedCollection new
+	classInfo := OrderedCollection new
     ] ifFalse:[
-        classInfo := classes asOrderedCollection
-                        collect:[:class |
-                            |i fn|
-
-                            i := ClassInfo new.
-                            i conditionForInclusion:#always.
-                            i className:class name.
-                            fn := class classFilename ? ((Smalltalk fileNameForClass:class) , '.st').
-                            i classFileName:fn.
-                            i
-                        ]
+	classInfo := classes asOrderedCollection
+			collect:[:class |
+			    |i fn|
+
+			    i := ClassInfo new.
+			    i conditionForInclusion:#always.
+			    i className:class name.
+			    fn := class classFilename ? ((Smalltalk fileNameForClass:class) , '.st').
+			    i classFileName:fn.
+			    i
+			]
     ].
     self propertyAt:#classInfo put:classInfo.
     ^ classInfo
@@ -2315,7 +2318,7 @@
 
     (classInfo := self classInfo) isNil ifTrue:[^ nil].
     (clsName := aClassOrClassName) isBehavior ifTrue:[
-        clsName := aClassOrClassName name
+	clsName := aClassOrClassName name
     ].
     ^ classInfo detect:[:i | i className = clsName] ifNone:nil.
 
@@ -2330,26 +2333,26 @@
     |classes classInfo|
 
     properties notNil ifTrue:[
-        classInfo := properties at:#classInfo ifAbsent:nil.
-        classInfo notNil ifTrue:[
-            classes := classInfo collect:[:i | i className]
-        ] ifFalse:[
-            classes := properties at:#classes ifAbsent:nil
-        ]
+	classInfo := properties at:#classInfo ifAbsent:nil.
+	classInfo notNil ifTrue:[
+	    classes := classInfo collect:[:i | i className]
+	] ifFalse:[
+	    classes := properties at:#classes ifAbsent:nil
+	]
     ].
 
     classes isNil ifTrue:[
-        classes := OrderedCollection new.
-        Smalltalk 
-            allClassesDo:[:aClass |
-                (true "aClass owningClass isNil"
-                and:[aClass isMeta not
-                and:[aClass package = packageName
-                and:[aClass isNamespace not or:[aClass == Smalltalk]]]]) ifTrue:[
-                    classes add:aClass
-                ]
-            ].
-        classes isEmpty ifTrue:[^ nil].
+	classes := OrderedCollection new.
+	Smalltalk 
+	    allClassesDo:[:aClass |
+		(true "aClass owningClass isNil"
+		and:[aClass isMeta not
+		and:[aClass package = packageName
+		and:[aClass isNamespace not or:[aClass == Smalltalk]]]]) ifTrue:[
+		    classes add:aClass
+		]
+	    ].
+	classes isEmpty ifTrue:[^ nil].
     ].
     ^ classes
 
@@ -2369,33 +2372,33 @@
 
     classes := self classes.
     classes notNil ifTrue:[
-        classes := classes asIdentitySet.
+	classes := classes asIdentitySet.
     ] ifFalse:[
-        classes := #()
+	classes := #()
     ].
 
     methods := IdentitySet new.
     Smalltalk allBehaviorsDo:[:cls |
-        |classToCheck|
-
-        classToCheck := cls.
+	|classToCheck|
+
+	classToCheck := cls.
 "/        cls isPrivate ifTrue:[
 "/            classToCheck := cls topOwningClass
 "/        ].
-        (classes isNil 
-        or:[((classes includes:classToCheck) 
-            or:[classes includes:classToCheck name]) not]) ifTrue:[
-            cls methodDictionary do:[:m |
-                m package = packageName ifTrue:[
-                    methods add:m
-                ]
-            ].
-            cls class methodDictionary do:[:m |
-                m package = packageName ifTrue:[
-                    methods add:m
-                ]
-            ].
-        ]
+	(classes isNil 
+	or:[((classes includes:classToCheck) 
+	    or:[classes includes:classToCheck name]) not]) ifTrue:[
+	    cls methodDictionary do:[:m |
+		m package = packageName ifTrue:[
+		    methods add:m
+		]
+	    ].
+	    cls class methodDictionary do:[:m |
+		m package = packageName ifTrue:[
+		    methods add:m
+		]
+	    ].
+	]
     ].
     ^ methods asArray
 
@@ -2418,30 +2421,30 @@
     "/ check for loaded class-library - assume loaded if present.
     binaryModule := ObjectMemory binaryModuleInfo detect:[:i | i package = self package] ifNone:nil.
     binaryModule notNil ifTrue:[
-        ^ true
+	^ true
     ].
 
     "/ check for all classes ...
     self classes do:[:aClassOrClassName |
-        aClassOrClassName isBehavior ifFalse:[
-            aClassOrClassName isSymbol ifTrue:[
-                (cls := Smalltalk at:aClassOrClassName) isNil ifTrue:[
-                    ^ false
-                ].
-                cls isBehavior ifFalse:[^ false].
-                cls isLoaded ifFalse:[^ false].
-            ] ifFalse:[
-                self halt.
-                ^ false
-            ]
-        ]
+	aClassOrClassName isBehavior ifFalse:[
+	    aClassOrClassName isSymbol ifTrue:[
+		(cls := Smalltalk at:aClassOrClassName) isNil ifTrue:[
+		    ^ false
+		].
+		cls isBehavior ifFalse:[^ false].
+		cls isLoaded ifFalse:[^ false].
+	    ] ifFalse:[
+		self halt.
+		^ false
+	    ]
+	]
     ].
 
     "/ check for all patches & extensions ...
     self methods do:[:aMethodInfo |
-        aMethodInfo method isNil ifTrue:[
-            ^ false
-        ].
+	aMethodInfo method isNil ifTrue:[
+	    ^ false
+	].
     ].
 
     ^ true
@@ -2459,33 +2462,33 @@
     |methodInfo methods|
 
     properties notNil ifTrue:[
-        methodInfo := properties at:#methodInfo ifAbsent:nil.
-        methodInfo notNil ifTrue:[^ methodInfo].
+	methodInfo := properties at:#methodInfo ifAbsent:nil.
+	methodInfo notNil ifTrue:[^ methodInfo].
     ].
 
     methods := self methods.
     methods size == 0 ifTrue:[
-        methodInfo := OrderedCollection new
+	methodInfo := OrderedCollection new
     ] ifFalse:[
-        methodInfo := methods asOrderedCollection
-                        collect:[:mthd |
-                            |i fn who className selector|
-
-                            mthd isMethod ifTrue:[   
-                                who := mthd who.
-                                className := who methodClass name.
-                                selector := who methodSelector.
-                                i := MethodInfo new.
-                                i conditionForInclusion:#always.
-                                i className:className.
-                                i methodName:className.
-                                fn := mthd sourceFilename.
-                                i fileName:fn.
-                                i
-                            ] ifFalse:[
-                                mthd "/ already a methodInfo
-                            ]
-                        ]
+	methodInfo := methods asOrderedCollection
+			collect:[:mthd |
+			    |i fn who className selector|
+
+			    mthd isMethod ifTrue:[   
+				who := mthd who.
+				className := who methodClass name.
+				selector := who methodSelector.
+				i := MethodInfo new.
+				i conditionForInclusion:#always.
+				i className:className.
+				i methodName:className.
+				fn := mthd sourceFilename.
+				i fileName:fn.
+				i
+			    ] ifFalse:[
+				mthd "/ already a methodInfo
+			    ]
+			]
     ].
     self propertyAt:#methodInfo put:methodInfo.
     ^ methodInfo
@@ -2500,41 +2503,41 @@
     |methods methodsInfo|
 
     properties notNil ifTrue:[
-        methodsInfo := properties at:#methodsInfo ifAbsent:nil.
-        methodsInfo notNil ifTrue:[
-            methods := methodsInfo collect:[:i | i className]
-        ] ifFalse:[
-            methods := properties at:#methods ifAbsent:nil
-        ]
+	methodsInfo := properties at:#methodsInfo ifAbsent:nil.
+	methodsInfo notNil ifTrue:[
+	    methods := methodsInfo collect:[:i | i className]
+	] ifFalse:[
+	    methods := properties at:#methods ifAbsent:nil
+	]
     ].
 
     methods isNil ifTrue:[
-        methods := OrderedCollection new.
-        Smalltalk allClassesDo:[:aClass |
-            (true "aClass owningClass isNil"
-            and:[aClass isMeta not
-            and:[aClass package ~= packageName
-            and:[aClass isNamespace not or:[aClass == Smalltalk]]]]) ifTrue:[
-            
-                aClass methodDictionary keysAndValuesDo:[:sel :mthd |
-                    mthd package = packageName ifTrue:[
-                        methods add:(MethodInfo new
-                                        className:aClass name;
-                                        methodName:sel;
-                                        yourself)
-                    ].
-                ].
-                aClass class methodDictionary keysAndValuesDo:[:sel :mthd |
-                    mthd package = packageName ifTrue:[
-                        methods add:(MethodInfo new
-                                        className:(aClass name , ' class');
-                                        methodName:sel;
-                                        yourself)
-                    ].
-                ]
-            ]
-        ].
-        methods isEmpty ifTrue:[^ #()].
+	methods := OrderedCollection new.
+	Smalltalk allClassesDo:[:aClass |
+	    (true "aClass owningClass isNil"
+	    and:[aClass isMeta not
+	    and:[aClass package ~= packageName
+	    and:[aClass isNamespace not or:[aClass == Smalltalk]]]]) ifTrue:[
+	    
+		aClass methodDictionary keysAndValuesDo:[:sel :mthd |
+		    mthd package = packageName ifTrue:[
+			methods add:(MethodInfo new
+					className:aClass name;
+					methodName:sel;
+					yourself)
+		    ].
+		].
+		aClass class methodDictionary keysAndValuesDo:[:sel :mthd |
+		    mthd package = packageName ifTrue:[
+			methods add:(MethodInfo new
+					className:(aClass name , ' class');
+					methodName:sel;
+					yourself)
+		    ].
+		]
+	    ]
+	].
+	methods isEmpty ifTrue:[^ #()].
     ].
     ^ methods
 
@@ -2563,23 +2566,23 @@
 
     d := (properties at:#directoryName) asFilename.
     d exists ifFalse:[
-        self error:'directory does not exist' mayProceed:true.
-        ^ self
+	self error:'directory does not exist' mayProceed:true.
+	^ self
     ].
     f := d construct:'.project'.
     s := f writeStream.
     s isNil ifTrue:[^ self].
     properties associationsDo:[:aProp |
-        (aProp == #directoryName) ifFalse:[
-            s nextChunkPut:('self at:' , aProp key storeString, 
-                               ' put:' , aProp value storeString).
-            s cr
-        ]
+	(aProp == #directoryName) ifFalse:[
+	    s nextChunkPut:('self at:' , aProp key storeString, 
+			       ' put:' , aProp value storeString).
+	    s cr
+	]
     ].
     s close
 
     "((Project new directory:'../projects/Clock') readSpec
-         directory:'../projects/xxx') saveSpec"
+	 directory:'../projects/xxx') saveSpec"
 ! !
 
 !Project methodsFor:'views'!
@@ -2606,9 +2609,9 @@
     "hide all views of this project"
 
     views notNil ifTrue:[
-        views do:[:aView |
-            aView notNil ifTrue:[aView unmap]
-        ]
+	views do:[:aView |
+	    aView notNil ifTrue:[aView unmap]
+	]
     ].
 
     "Modified: 3.5.1996 / 23:48:51 / stefan"
@@ -2618,7 +2621,7 @@
     "remove a view from this projects set of views"
 
     views notNil ifTrue:[
-        views remove:aView ifAbsent:nil
+	views remove:aView ifAbsent:nil
     ]
 
     "Modified: 14.2.1997 / 15:37:20 / cg"
@@ -2628,9 +2631,9 @@
     "show all views of this project"
 
     views notNil ifTrue:[
-        views do:[:aView |
-            aView notNil ifTrue:[aView remap]
-        ]
+	views do:[:aView |
+	    aView notNil ifTrue:[aView remap]
+	]
     ].
 
     "Modified: 3.5.1996 / 23:59:10 / stefan"
@@ -2738,6 +2741,6 @@
 !Project class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Project.st,v 1.110 1999-09-25 10:33:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Project.st,v 1.111 1999-09-25 13:20:37 cg Exp $'
 ! !
 Project initialize!