care for inheritance order, when saving a project file.
authorClaus Gittinger <cg@exept.de>
Sun, 03 Oct 1999 16:37:37 +0200
changeset 4832 d335c43bf297
parent 4831 98113bc11cdd
child 4833 5652aec1b08a
care for inheritance order, when saving a project file.
Project.st
--- a/Project.st	Sun Oct 03 11:26:06 1999 +0200
+++ b/Project.st	Sun Oct 03 16:37:37 1999 +0200
@@ -20,15 +20,15 @@
 	category:'System-Support'
 !
 
-Object subclass:#MethodInfo
-	instanceVariableNames:'conditionForInclusion methodName className fileName'
+Object subclass:#ClassInfo
+	instanceVariableNames:'conditionForInclusion className classFileName'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:Project
 !
 
-Object subclass:#ClassInfo
-	instanceVariableNames:'conditionForInclusion className classFileName'
+Object subclass:#MethodInfo
+	instanceVariableNames:'conditionForInclusion methodName className fileName'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:Project
@@ -1112,7 +1112,7 @@
      Actually, the format is the same as used for resources (i.e. key - value pairs)
      and the code below could be much simpler - if there where no humans to read it ..."
 
-    |s coll first maxLen t defNS methodsFile|
+    |s coll first maxLen t defNS methodsFile classes|
 
     s := aStream.
 
@@ -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:'
@@ -1275,40 +1275,44 @@
 
     s nextPutAll:'classes'; tab.
 
-    coll := self classInfo.
-    coll size = 0 ifTrue:[
-	s nextPutLine:'#()'. 
+    classes := self classesInOrderFor:'save ''prj''-file.'.
+    classes isNil ifTrue:[^ self].
+
+    classes size = 0 ifTrue:[
+        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 := classes inject:0 into:[:maxSoFar :aClass |
+                                        |clsName|
+
+                                        clsName := aClass name.
+                                        maxSoFar max:clsName storeString size
+                                     ].
+
+        classes do:[:aClass |
+            |clsInfo clsName fileName cond|
+
+            clsInfo := self classInfoFor:aClass.
+
+            clsName := aClass name.
+            fileName := clsInfo classFileName.
+            fileName = (clsName , '.st') ifTrue:[
+                fileName := nil
+            ].
+            cond := (clsInfo 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 +1327,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 +1368,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:')'.
     ].
 
     "
@@ -1388,65 +1392,73 @@
     OperatingSystem executeCommand:('cd ' , self directory , ' ; make')
 !
 
-createLoadAllFile
-    "creates a 'loadAll' file, which will load all classes
-     of the project - this loadAll file is supposed to be located
-     in the projects source directory."
-
-    |d f out in topName classes classInfo numBad firstBad msg 
-     methodsFile prerequisitePackages|
+classesInOrderFor:whatMsg
+    |classes numBad firstBad msg|
 
     classes := self classes.
     numBad := 0.
     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 ' , whatMsg.
+        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.
+        ^ nil.
     ].
 
     "/ to not list private classes
     classes := classes select:[:cls | cls owningClass isNil].
     classes := classes copy topologicalSort:[:a :b | b isSubclassOf:a].
 
+    ^ classes
+!
+
+createLoadAllFile
+    "creates a 'loadAll' file, which will load all classes
+     of the project - this loadAll file is supposed to be located
+     in the projects source directory."
+
+    |d f out in topName classes classInfo    
+     methodsFile prerequisitePackages|
+
+    classes := self classesInOrderFor:'generate ''loadAll''-file.'.
+    classes isNil ifTrue:[^ self].
+
     Transcript showCR:'creating loadAll file'.
 
     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:'"/
@@ -1465,29 +1477,29 @@
 "/ 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 nextPutLine:''.
-	out nextPutLine:'"/ Smalltalk loadPackage:''module:directory''.'.
-	out nextPutLine:'"/ Smalltalk loadPackage:''....''.'.
+        out nextPutLine:''.
+        out nextPutLine:'"/ Smalltalk loadPackage:''module:directory''.'.
+        out nextPutLine:'"/ Smalltalk loadPackage:''....''.'.
     ] ifFalse:[
-	out cr.
-	prerequisitePackages do:[:packName |
-	    out nextPutLine:'Smalltalk loadPackage:''' , packName , '''.'.
-	]
+        out cr.
+        prerequisitePackages do:[:packName |
+            out nextPutLine:'Smalltalk loadPackage:''' , packName , '''.'.
+        ]
     ].
 
     out nextPutAll:'!!
@@ -1503,23 +1515,23 @@
 '.
 
     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:'''';
-	    cr.
+         out 
+            nextPutAll:'  ''';
+            nextPutAll:methodsFile;
+            nextPutAll:'''';
+            cr.
     ].
 
     out nextPutAll:') asOrderedCollection.
@@ -1528,14 +1540,14 @@
     |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 nextPutLine:('        loaded add:''' , methodsFile , '''.').
+        out nextPutLine:('        loaded add:''' , methodsFile , '''.').
     ].
     out nextPutAll:'        files := files asOrderedCollection select:[:f| (loaded includes:f) not].
     ].
@@ -1592,45 +1604,10 @@
     "creates an nt.mak file"
 
     |d f s type appName libName startUpClass startUpSelector
-     topName classes numBad firstBad msg methodsFile|
-
-    classes := self classes.
-    numBad := 0.
-    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
-                                        ]
-                              ].
-    numBad ~~ 0 ifTrue:[
-        msg := 'Cannot generate ''nt.mak''-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
-    classes := classes select:[:cls | cls owningClass isNil].
-    classes := classes copy topologicalSort:[:a :b | b isSubclassOf:a].
+     topName classes methodsFile|
+
+    classes := self classesInOrderFor:'generate ''nt.mak''-file.'.
+    classes isNil ifTrue:[^ self].
 
     topName := self findTopFrom:directoryName.
 
@@ -2019,45 +1996,10 @@
     "creates a Make.proto file"
 
     |d f s type appName libName startUpClass startUpSelector
-     topName classes numBad firstBad msg methodsFile|
-
-    classes := self classes.
-    numBad := 0.
-    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
-					]
-			      ].
-    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.
-    ].
-
-    "/ to not list private classes
-    classes := classes select:[:cls | cls owningClass isNil].
-    classes := classes copy topologicalSort:[:a :b | b isSubclassOf:a].
+     topName classes methodsFile|
+
+    classes := self classesInOrderFor:'generate ''Make.proto''-file.'.
+    classes isNil ifTrue:[^ self].
 
     topName := self findTopFrom:directoryName.
 
@@ -2067,12 +2009,12 @@
     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'. 
     s nextPutLine:'$'.
@@ -2161,13 +2103,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:, 
@@ -2235,31 +2177,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.
 
@@ -2321,16 +2263,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
@@ -3071,6 +3013,56 @@
     "Modified: 14.2.1997 / 15:38:47 / cg"
 ! !
 
+!Project::ClassInfo methodsFor:'accessing'!
+
+classFileName
+    "return the value of the instance variable 'classFileName' (automatically generated)"
+
+    ^ classFileName!
+
+classFileName:something
+    "set the value of the instance variable 'classFileName' (automatically generated)"
+
+    classFileName := something.!
+
+className
+    "return the value of the instance variable 'className' (automatically generated)"
+
+    ^ className!
+
+className:something
+    "set the value of the instance variable 'className' (automatically generated)"
+
+    className := something.!
+
+conditionForInclusion
+    "return the value of the instance variable 'conditionForInclusion' (automatically generated)"
+
+    ^ conditionForInclusion!
+
+conditionForInclusion:something
+    "set the value of the instance variable 'conditionForInclusion' (automatically generated)"
+
+    conditionForInclusion := something.! !
+
+!Project::ClassInfo methodsFor:'printing & storing'!
+
+displayString
+    ^ 'ClassInfo: ' , className
+! !
+
+!Project::ClassInfo methodsFor:'queries'!
+
+theClass
+    |cls|
+
+    cls := Smalltalk classNamed:className.
+    cls isNil ifTrue:[ ^ nil].
+    ^ cls
+
+    "Created: / 26.9.1999 / 13:39:00 / cg"
+! !
+
 !Project::MethodInfo methodsFor:'accessing'!
 
 className
@@ -3140,59 +3132,9 @@
     "Created: / 26.9.1999 / 13:39:07 / cg"
 ! !
 
-!Project::ClassInfo methodsFor:'accessing'!
-
-classFileName
-    "return the value of the instance variable 'classFileName' (automatically generated)"
-
-    ^ classFileName!
-
-classFileName:something
-    "set the value of the instance variable 'classFileName' (automatically generated)"
-
-    classFileName := something.!
-
-className
-    "return the value of the instance variable 'className' (automatically generated)"
-
-    ^ className!
-
-className:something
-    "set the value of the instance variable 'className' (automatically generated)"
-
-    className := something.!
-
-conditionForInclusion
-    "return the value of the instance variable 'conditionForInclusion' (automatically generated)"
-
-    ^ conditionForInclusion!
-
-conditionForInclusion:something
-    "set the value of the instance variable 'conditionForInclusion' (automatically generated)"
-
-    conditionForInclusion := something.! !
-
-!Project::ClassInfo methodsFor:'printing & storing'!
-
-displayString
-    ^ 'ClassInfo: ' , className
-! !
-
-!Project::ClassInfo methodsFor:'queries'!
-
-theClass
-    |cls|
-
-    cls := Smalltalk classNamed:className.
-    cls isNil ifTrue:[ ^ nil].
-    ^ cls
-
-    "Created: / 26.9.1999 / 13:39:00 / cg"
-! !
-
 !Project class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Project.st,v 1.117 1999-09-26 22:23:22 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Project.st,v 1.118 1999-10-03 14:37:37 cg Exp $'
 ! !
 Project initialize!