code cleanup
authorClaus Gittinger <cg@exept.de>
Tue, 07 Nov 2006 12:56:31 +0100
changeset 1939 babab41fc8e8
parent 1938 8d0163055b68
child 1940 72cc74daf8fc
code cleanup
STCCompilerInterface.st
--- a/STCCompilerInterface.st	Tue Nov 07 12:22:35 2006 +0100
+++ b/STCCompilerInterface.st	Tue Nov 07 12:56:31 2006 +0100
@@ -10,11 +10,12 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libcomp' }"
 
 Object subclass:#STCCompilerInterface
-	instanceVariableNames:'originator parserFlags'
+	instanceVariableNames:'originator parserFlags initName theNonMetaclassToCompileFor
+		classToCompileFor stFileName cFileName oFileName stcFlags cFlags
+		stcPath ccPath requestor methodCategory executionStatus package'
 	classVariableNames:'SequenceNumber Verbose'
 	poolDictionaries:''
 	category:'System-Compiler'
@@ -139,19 +140,14 @@
 
 !STCCompilerInterface methodsFor:'machine code generation'!
 
-compileToMachineCode:aString forClass:aClass selector:selector inCategory:cat 
-                             notifying:requestor install:install skipIfSame:skipIfSame silent:silent
+compileToMachineCode:aString forClass:aClass selector:selector inCategory:categoryArg 
+                             notifying:requestorArg install:install skipIfSame:skipIfSame silent:silent
     "this is called to compile primitive code.
      This is EXPERIMENTAL and going to be changed to raise an error,
      an redefined in subclasses which can do it (either by direct compilation, or by calling
-     the external stc do do it.
-     For a description of the arguments, see compile:forClass....."
+     the external stc do do it)."
 
-    |stFileName stream handle stcFlags cFlags def
-     command oFileName cFileName
-     initName oldMethod newMethod ok status className sep class stcPath ccPath 
-     errorStream errorMessages eMsg moduleFileName 
-     mapFileName libFileName pkg libDir incDir incDirArg lNr|
+    |handle oldMethod newMethod ok className moduleFileName|
 
     install ifFalse:[
         "/ cannot do it uninstalled. reason:
@@ -160,270 +156,44 @@
         "/ (because the first unload would unload the second version too)
         ^ #CannotLoad
     ].
-
-    self ensureModuleDirectoryExists.
-
-    ObjectFileLoader isNil ifTrue:[^ #CannotLoad].
     parserFlags stcCompilation == #never ifTrue:[^ #CannotLoad].
 
-    (stcPath := self incrementalStcPath) isNil ifTrue:[
-        originator parseError:'no stc compiler available - cannot create machine code' position:1.
-        ^ #CannotLoad
-    ].
-    (ccPath := parserFlags ccPath) isNil ifTrue:[
-        originator parseError:'no cc compiler available - cannot create machine code' position:1.
-        ^ #CannotLoad
-    ].
+    classToCompileFor := aClass.
+    requestor := requestorArg.
+    methodCategory := categoryArg.
 
-    (ObjectFileLoader notNil and:[ObjectFileLoader canLoadObjectFiles]) ifFalse:[
-        originator parseError:'no dynamic loader configured - cannot create machine code' position:1.
-        ^ #CannotLoad
-    ].
+    self ensureModuleDirectoryExists.
+    self ensureExternalToolsArePresent ifFalse:[^ #CannotLoad].
 
-    class := aClass theNonMetaclass.
-    self ensureSuperClassesAreLoadedOf:class.
-    class privateClassesSorted do:[:aPrivateClass |
+    theNonMetaclassToCompileFor := classToCompileFor theNonMetaclass.
+    self ensureSuperClassesAreLoadedOf:theNonMetaclassToCompileFor.
+    theNonMetaclassToCompileFor privateClassesSorted do:[:aPrivateClass |
         self ensureSuperClassesAreLoadedOf:aPrivateClass.
     ].
 
-    "/ generate a unique name, consisting of my processID and a sequence number
-    "/ the processId is added to allow filein of modules from different
-    "/ lifes
-
-    SequenceNumber := (SequenceNumber ? 0) + 1.
-
-    initName := 'm_' , OperatingSystem getProcessId printString, '_' , SequenceNumber printString.
-
-    stFileName := (Filename currentDirectory construct:(initName , '.st')) name. 
-    [
-        stream := stFileName asFilename writeStream.
-    ] on:FileStream openErrorSignal do:[:ex|
-        originator parseError:'cannot create temporary sourcefile for compilation'.
-        ^ #CannotLoad
+    (classToCompileFor isNil 
+    or:[parserFlags allowExtensionsToPrivateClasses 
+    or:[classToCompileFor owningClass isNil]]) ifTrue:[
+        (requestor respondsTo:#packageToInstall) ifFalse:[
+            package := Class packageQuerySignal query.
+        ] ifTrue:[
+            package := requestor packageToInstall
+        ].
+    ] ifFalse:[
+        package := classToCompileFor owningClass package
     ].
 
     [
-        |definedClasses|
-
-        definedClasses := IdentitySet new.
-
-        sep := stream class chunkSeparator.
-
-        Class fileOutNameSpaceQuerySignal answer:true
-        do:[
-            self 
-                fileOutAllDefinitionsOf:class 
-                to:stream 
-                rememberIn:definedClasses.
-
-            class privateClassesSorted do:[:aPrivateClass |
-                self 
-                    fileOutAllDefinitionsOf:aPrivateClass 
-                    to:stream 
-                    rememberIn:definedClasses.
-            ].
-            class fileOutPrimitiveDefinitionsOn:stream.
-        ].
-
-        (aClass isNil or:[parserFlags allowExtensionsToPrivateClasses or:[aClass owningClass isNil]]) ifTrue:[
-            (requestor respondsTo:#packageToInstall) ifFalse:[
-                pkg := Class packageQuerySignal query.
-            ] ifTrue:[
-                pkg := requestor packageToInstall
-            ].
-        ] ifFalse:[
-            pkg := aClass owningClass package
-        ].
-false ifTrue:[
-        stream cr.
-        stream nextPutLine:'"{ Package: ''' , pkg , ''' }"'.
-        stream cr.
-].
-
-        stream nextPut:sep.
-        className := class name.
-
-        stream nextPutAll:className.
-        aClass isMeta ifTrue:[
-            stream nextPutAll:' class'.
-        ].
-        stream nextPutAll:' methodsFor:'''; nextPutAll:cat; nextPutAll:''''.
-        stream nextPut:sep; cr.
-
-        stream nextPutLine:'"{ Line: 0 }"'; 
-               nextChunkPut:aString;
-               space; nextPut:sep.
-
-        stream close.
-
-        "
-         call stc to compile it
-        "
-        oFileName := stFileName asFilename withoutSuffix name , (ObjectFileLoader objectFileExtension).
-        cFileName := (stFileName asFilename withSuffix:'c') name. 
-        mapFileName := (stFileName asFilename withSuffix:'map') name. 
-        libFileName := (stFileName asFilename withSuffix:'lib') name. 
-        oFileName asFilename delete.
-        cFileName asFilename delete.
-
-        "/ stcFlags := '-commonSymbols +sharedLibCode +newIncremental -E:errorOutput -N' , initName .
-        stcFlags := '+newIncremental -E:errorOutput -N' , initName .
-        cFlags := OperatingSystem getOSDefine.
-        cFlags isNil ifTrue:[
-            cFlags := ''
-        ].
-        (def := OperatingSystem getCPUDefine) notNil ifTrue:[
-            cFlags := cFlags , ' ' , def
-        ].
-
-        parserFlags stcCompilationDefines notNil ifTrue:[
-            cFlags := cFlags , ' ' , parserFlags stcCompilationDefines
-        ].
-        parserFlags stcCompilationIncludes notNil ifTrue:[
-            stcFlags := parserFlags stcCompilationIncludes , ' ' , stcFlags.
-            cFlags := cFlags , ' ' , parserFlags stcCompilationIncludes.
-
-            "/ if STX_LIBDIR is defined, and not in passed argument,
-            "/ add it here.
-
-            libDir := OperatingSystem getEnvironment:'STX_LIBDIR'.
-            (libDir notNil and:[libDir asFilename exists]) ifTrue:[
-                incDir := libDir asFilename construct:'include'.
-                incDir exists ifTrue:[
-                    incDirArg := '-I' , incDir pathName.
-                    (parserFlags stcCompilationIncludes asCollectionOfWords includes:incDirArg) ifFalse:[
-                        stcFlags := stcFlags , ' ' , incDirArg.
-                        cFlags := cFlags , ' ' , incDirArg.
-                    ]
-                ]
-            ].
-        ].
-        parserFlags stcCompilationOptions notNil ifTrue:[
-            stcFlags := parserFlags stcCompilationOptions , ' ' , stcFlags
-        ].
-        parserFlags ccCompilationOptions notNil ifTrue:[
-            cFlags := cFlags , ' ' , parserFlags ccCompilationOptions
-        ].
-
-        command := stcPath , ' ' , stcFlags , ' -C ' , stFileName.
-
-        Verbose == true ifTrue:[
-            'executing: ' infoPrint. command infoPrintCR.
-        ].
-        errorStream := 'errorOutput' asFilename writeStream.
-
-        originator activityNotification:'compiling (stc)'.
-        ok := OperatingSystem 
-                    executeCommand:command 
-                    inputFrom:nil
-                    outputTo:errorStream
-                    errorTo:errorStream
-                    onError:[:stat| 
-                                status := stat.
-                                false
-                            ].
-
-        cFileName asFilename exists ifTrue:[
-            ok ifFalse:[
-                'Compiler [info]: oops - system says stc failed - but c-file is there ...' infoPrintCR.
-                ok := true
-            ]
-        ] ifFalse:[
-            ok ifTrue:[
-                'Compiler [info]: oops - system says stc ok - but no c-file is there ...' infoPrintCR.
-            ].
-            ok := false
-        ].
-
+        self generateSTSource:aString.
+        self setupCompilationCommandArguments.
+        ok := self compileToC.
         ok ifTrue:[
             "/ now compile to machine code
-
-            command := ccPath , ' ' , cFlags , ' -D__INCREMENTAL_COMPILE__ -c ' , cFileName.
-            Verbose == true ifTrue:[
-                'executing: ' infoPrint. command infoPrintCR.
-            ].
-            originator activityNotification:'compiling (' , ccPath , ')'.
-            ok := OperatingSystem 
-                        executeCommand:command 
-                        inputFrom:nil
-                        outputTo:errorStream
-                        errorTo:errorStream
-                        onError:[:stat| 
-                                    status := stat.
-                                    false
-                                ].
-
-            oFileName asFilename exists ifTrue:[
-                ok ifFalse:[
-                    'Compiler [info]: system says compile failed - but o-file is there ...' infoPrintCR.
-                    ok := true
-                ]
-            ] ifFalse:[
-                ok ifTrue:[
-                    'Compiler [info]: system says compile ok - but no o-file is there ...' infoPrintCR.
-                ].
-                ok := false
-            ].
+            ok := self compileToObj.
         ].
 
         ok ifFalse:[
-            (status notNil and:[status couldNotExecute]) ifTrue:[
-                eMsg := 'oops, no STC - cannot create machine code'
-            ] ifFalse:[
-                errorMessages := 'errorOutput' asFilename contents.
-                errorMessages notNil ifTrue:[
-                    errorMessages := errorMessages reject:[:line | line includesString:'Warning:'].
-
-                    errorMessages size > 20 ifTrue:[
-                        errorMessages := errorMessages select:[:line | line asLowercase startsWith:'error'].
-                        errorMessages size > 20 ifTrue:[
-                            errorMessages := (errorMessages copyTo:20) copyWith:'... more messages skipped'
-                        ].
-                    ].
-"/                    errorMessages := errorMessages collect:[:line |
-"/                        (line startsWith:(stFileName , ':')) ifTrue:[
-"/                            'Line: ' , (line copyFrom:(stFileName size + 2))
-"/                        ] ifFalse:[
-"/                            line
-"/                        ]
-"/                      ].
-                ].
-                errorMessages isNil ifTrue:[
-                    errorMessages := #('')
-                ].
-
-                "/ try to extract a line number"
-                (errorMessages contains:[:line | line includesString:'Borland']) ifTrue:[
-                    |i i2 s|
-                    i := errorMessages findFirst:[:l | l startsWith:(cFileName,':')].
-                    i ~~ 0 ifTrue:[
-                        ((errorMessages at:i+1) startsWith:'Error') ifTrue:[
-                            i2 := (errorMessages at:i+1) indexOfSubCollection:(stFileName).
-                            i2 ~~ 0 ifTrue:[
-                                s := (errorMessages at:i+1) copyFrom:(i2+stFileName size+1).
-                                s := s readStream.
-                                lNr := Integer readFrom:s.
-                                s skipSeparators.
-                            ].    
-                        ]
-                    ].
-                ].
-
-                errorMessages isEmpty ifTrue:[
-                    eMsg := 'Error during compilation:\\Unspecified error (no output)' withCRs
-                ] ifFalse:[
-                    eMsg := 'Error during compilation:\\' withCRs ,
-                            (errorMessages asStringCollection asString).
-                ].
-                "/ eMsg := eMsg withCRs
-            ].
-            originator activityNotification:'compilation failed'.
-            lNr notNil ifTrue:[
-                originator parseError:eMsg line:lNr
-            ] ifFalse:[
-                originator parseError:eMsg position:1.
-            ].
-            originator activityNotification:''.
+            self reportCompilationError.
             ^ #Error
         ].
 
@@ -457,8 +227,8 @@
             ^ #CannotLoad
         ].
 
-        oldMethod := aClass compiledMethodAt:selector.
-        oldMethod notNil ifTrue:[pkg := oldMethod package].
+        oldMethod := classToCompileFor compiledMethodAt:selector.
+        oldMethod notNil ifTrue:[package := oldMethod package].
 
         "
          load the method objectfile
@@ -475,16 +245,16 @@
         "
          did it work ?
         "
-        newMethod := aClass compiledMethodAt:selector.
+        newMethod := classToCompileFor compiledMethodAt:selector.
 
         "/ if install is false, we have to undo the install (which is always done, when loading machine code)
         install ifFalse:[
             oldMethod isNil ifTrue:[
-                aClass removeSelector:selector
+                classToCompileFor removeSelector:selector
             ] ifFalse:[
                 newMethod setPackage:oldMethod package.
-                aClass addSelector:selector withMethod:oldMethod.
-                oldMethod setPackage:pkg.
+                classToCompileFor addSelector:selector withMethod:oldMethod.
+                oldMethod setPackage:package.
             ]
         ].
 
@@ -494,19 +264,19 @@
             ].
 
             newMethod source:aString string.
-            newMethod setPackage:pkg.
+            newMethod setPackage:package.
 "/            Project notNil ifTrue:[
 "/                newMethod package:(Project currentPackageName)
 "/            ].
 
-    "/        aClass updateRevisionString.
+    "/        classToCompileFor updateRevisionString.
             install ifTrue:[
-                aClass addChangeRecordForMethod:newMethod fromOld:oldMethod.
+                classToCompileFor addChangeRecordForMethod:newMethod fromOld:oldMethod.
 
                 "/ kludge-sigh: must send change messages manually here (stc-loaded code does not do it)
                 "/ see addMethod:... in ClassDescription
-                aClass changed:#methodDictionary with:(Array with:selector with:oldMethod).
-                Smalltalk changed:#methodInClass with:(Array with:aClass with:selector with:oldMethod).
+                classToCompileFor changed:#methodDictionary with:(Array with:selector with:oldMethod).
+                Smalltalk changed:#methodInClass with:(Array with:classToCompileFor with:selector with:oldMethod).
             ].
 
             (silent or:[Smalltalk silentLoading == true]) ifFalse:[
@@ -585,9 +355,112 @@
      m inspect
     "
 
-    "Modified: / 14.9.1995 / 22:33:04 / claus"
-    "Modified: / 19.3.1999 / 08:31:42 / stefan"
-    "Modified: / 10.11.2001 / 01:46:00 / cg"
+    "Modified: / 14-09-1995 / 22:33:04 / claus"
+    "Modified: / 19-03-1999 / 08:31:42 / stefan"
+    "Modified: / 07-11-2006 / 12:45:52 / cg"
+! !
+
+!STCCompilerInterface methodsFor:'machine code generation-helpers'!
+
+compileToC
+    "compile st to C using stc"
+
+    |command errorStream ok|
+
+    command := stcPath , ' ' , stcFlags , ' -C ' , stFileName.
+    errorStream := 'errorOutput' asFilename writeStream.
+
+    Verbose == true ifTrue:[
+        'executing: ' infoPrint. command infoPrintCR.
+    ].
+
+    originator activityNotification:'compiling (stc)'.
+    ok := OperatingSystem 
+                executeCommand:command 
+                inputFrom:nil
+                outputTo:errorStream
+                errorTo:errorStream
+                onError:[:stat| 
+                            executionStatus := stat.
+                            false
+                        ].
+
+    errorStream close.
+
+    cFileName asFilename exists ifTrue:[
+        ok ifFalse:[
+            'Compiler [info]: oops - system says stc failed - but c-file is there ...' infoPrintCR.
+            ok := true
+        ]
+    ] ifFalse:[
+        ok ifTrue:[
+            'Compiler [info]: oops - system says stc ok - but no c-file is there ...' infoPrintCR.
+        ].
+        ok := false
+    ].
+    ^ ok
+
+    "Created: / 07-11-2006 / 12:11:24 / cg"
+!
+
+compileToObj
+    "compile C to obj, using cc"
+
+    |command errorStream ok|
+
+    errorStream := 'errorOutput' asFilename writeStream.
+
+    command := ccPath , ' ' , cFlags , ' -D__INCREMENTAL_COMPILE__ -c ' , cFileName.
+
+    Verbose == true ifTrue:[
+        'executing: ' infoPrint. command infoPrintCR.
+    ].
+    originator activityNotification:'compiling (' , ccPath , ')'.
+    ok := OperatingSystem 
+                executeCommand:command 
+                inputFrom:nil
+                outputTo:errorStream
+                errorTo:errorStream
+                onError:[:stat| 
+                            executionStatus := stat.
+                            false
+                        ].
+
+    errorStream close.
+
+    oFileName asFilename exists ifTrue:[
+        ok ifFalse:[
+            'Compiler [info]: system says compile failed - but o-file is there ...' infoPrintCR.
+            ok := true
+        ]
+    ] ifFalse:[
+        ok ifTrue:[
+            'Compiler [info]: system says compile ok - but no o-file is there ...' infoPrintCR.
+        ].
+        ok := false
+    ].
+    ^ ok
+
+    "Created: / 07-11-2006 / 12:14:51 / cg"
+!
+
+ensureExternalToolsArePresent
+    (stcPath := self incrementalStcPath) isNil ifTrue:[
+        originator parseError:'no stc compiler available - cannot create machine code' position:1.
+        ^ false
+    ].
+    (ccPath := parserFlags ccPath) isNil ifTrue:[
+        originator parseError:'no cc compiler available - cannot create machine code' position:1.
+        ^ false
+    ].
+
+    (ObjectFileLoader notNil and:[ObjectFileLoader canLoadObjectFiles]) ifFalse:[
+        originator parseError:'no dynamic loader configured - cannot create machine code' position:1.
+        ^ false
+    ].
+    ^ true
+
+    "Created: / 07-11-2006 / 12:31:48 / cg"
 !
 
 ensureModuleDirectoryExists
@@ -662,12 +535,194 @@
 
     aClass allSuperclasses reverseDo:defineAction.
     defineAction value:aClass.
+!
+
+generateSTSource:aString 
+    |stream definedClasses sep className|
+
+    "/ generate a unique name, consisting of my processID and a sequence number
+    "/ the processId is added to allow filein of modules from different
+    "/ lifes
+
+    SequenceNumber := (SequenceNumber ? 0) + 1.
+
+    initName := 'm_' , OperatingSystem getProcessId printString, '_' , SequenceNumber printString.
+
+    stFileName := (Filename currentDirectory construct:(initName , '.st')) name. 
+    [
+        stream := stFileName asFilename writeStream.
+    ] on:FileStream openErrorSignal do:[:ex|
+        originator parseError:'cannot create temporary sourcefile for compilation'.
+        ^ #CannotLoad
+    ].
+
+    definedClasses := IdentitySet new.
+
+    sep := stream class chunkSeparator.
+
+    Class fileOutNameSpaceQuerySignal answer:true
+    do:[
+        self 
+            fileOutAllDefinitionsOf:theNonMetaclassToCompileFor 
+            to:stream 
+            rememberIn:definedClasses.
+
+        theNonMetaclassToCompileFor privateClassesSorted do:[:aPrivateClass |
+            self 
+                fileOutAllDefinitionsOf:aPrivateClass 
+                to:stream 
+                rememberIn:definedClasses.
+        ].
+        theNonMetaclassToCompileFor fileOutPrimitiveDefinitionsOn:stream.
+    ].
+
+false ifTrue:[
+        stream cr.
+        stream nextPutLine:'"{ Package: ''' , package , ''' }"'.
+        stream cr.
+].
+
+    stream nextPut:sep.
+    className := theNonMetaclassToCompileFor name.
+
+    stream nextPutAll:className.
+    classToCompileFor isMeta ifTrue:[
+        stream nextPutAll:' class'.
+    ].
+    stream nextPutAll:' methodsFor:'''; nextPutAll:methodCategory; nextPutAll:''''.
+    stream nextPut:sep; cr.
+
+    stream nextPutLine:'"{ Line: 0 }"'; 
+           nextChunkPut:aString;
+           space; nextPut:sep.
+
+    stream close.
+
+    "Modified: / 07-11-2006 / 12:45:04 / cg"
+!
+
+reportCompilationError
+    |eMsg errorMessages lNr|
+
+    (executionStatus notNil and:[executionStatus couldNotExecute]) ifTrue:[
+        eMsg := 'oops, no STC - cannot create machine code'
+    ] ifFalse:[
+        errorMessages := 'errorOutput' asFilename contents.
+        OperatingSystem removeFile:'errorOutput'.
+
+        errorMessages notNil ifTrue:[
+            errorMessages := errorMessages reject:[:line | line includesString:'Warning:'].
+
+            errorMessages size > 20 ifTrue:[
+                errorMessages := errorMessages select:[:line | line asLowercase startsWith:'error'].
+                errorMessages size > 20 ifTrue:[
+                    errorMessages := (errorMessages copyTo:20) copyWith:'... more messages skipped'
+                ].
+            ].
+"/                    errorMessages := errorMessages collect:[:line |
+"/                        (line startsWith:(stFileName , ':')) ifTrue:[
+"/                            'Line: ' , (line copyFrom:(stFileName size + 2))
+"/                        ] ifFalse:[
+"/                            line
+"/                        ]
+"/                      ].
+        ].
+        errorMessages isNil ifTrue:[
+            errorMessages := #('')
+        ].
+
+        "/ try to extract a line number"
+        (errorMessages contains:[:line | line includesString:'Borland']) ifTrue:[
+            |i i2 s|
+            i := errorMessages findFirst:[:l | l startsWith:(cFileName,':')].
+            i ~~ 0 ifTrue:[
+                ((errorMessages at:i+1) startsWith:'Error') ifTrue:[
+                    i2 := (errorMessages at:i+1) indexOfSubCollection:(stFileName).
+                    i2 ~~ 0 ifTrue:[
+                        s := (errorMessages at:i+1) copyFrom:(i2+stFileName size+1).
+                        s := s readStream.
+                        lNr := Integer readFrom:s.
+                        s skipSeparators.
+                    ].    
+                ]
+            ].
+        ].
+
+        errorMessages isEmpty ifTrue:[
+            eMsg := 'Error during compilation:\\Unspecified error (no output)' withCRs
+        ] ifFalse:[
+            eMsg := 'Error during compilation:\\' withCRs ,
+                    (errorMessages asStringCollection asString).
+        ].
+        "/ eMsg := eMsg withCRs
+    ].
+    originator activityNotification:'compilation failed'.
+    lNr notNil ifTrue:[
+        originator parseError:eMsg line:lNr
+    ] ifFalse:[
+        originator parseError:eMsg position:1.
+    ].
+    originator activityNotification:''.
+
+    "Created: / 07-11-2006 / 12:29:04 / cg"
+!
+
+setupCompilationCommandArguments
+    |mapFileName libFileName def libDir incDir incDirArg|
+
+    oFileName := stFileName asFilename withoutSuffix name , (ObjectFileLoader objectFileExtension).
+    cFileName := (stFileName asFilename withSuffix:'c') name. 
+    mapFileName := (stFileName asFilename withSuffix:'map') name. 
+    libFileName := (stFileName asFilename withSuffix:'lib') name. 
+    oFileName asFilename delete.
+    cFileName asFilename delete.
+
+    "/ stcFlags := '-commonSymbols +sharedLibCode +newIncremental -E:errorOutput -N' , initName .
+    stcFlags := '+newIncremental -E:errorOutput -N' , initName .
+    cFlags := OperatingSystem getOSDefine.
+    cFlags isNil ifTrue:[
+        cFlags := ''
+    ].
+    (def := OperatingSystem getCPUDefine) notNil ifTrue:[
+        cFlags := cFlags , ' ' , def
+    ].
+
+    parserFlags stcCompilationDefines notNil ifTrue:[
+        cFlags := cFlags , ' ' , parserFlags stcCompilationDefines
+    ].
+    parserFlags stcCompilationIncludes notNil ifTrue:[
+        stcFlags := parserFlags stcCompilationIncludes , ' ' , stcFlags.
+        cFlags := cFlags , ' ' , parserFlags stcCompilationIncludes.
+
+        "/ if STX_LIBDIR is defined, and not in passed argument,
+        "/ add it here.
+
+        libDir := OperatingSystem getEnvironment:'STX_LIBDIR'.
+        (libDir notNil and:[libDir asFilename exists]) ifTrue:[
+            incDir := libDir asFilename construct:'include'.
+            incDir exists ifTrue:[
+                incDirArg := '-I' , incDir pathName.
+                (parserFlags stcCompilationIncludes asCollectionOfWords includes:incDirArg) ifFalse:[
+                    stcFlags := stcFlags , ' ' , incDirArg.
+                    cFlags := cFlags , ' ' , incDirArg.
+                ]
+            ]
+        ].
+    ].
+    parserFlags stcCompilationOptions notNil ifTrue:[
+        stcFlags := parserFlags stcCompilationOptions , ' ' , stcFlags
+    ].
+    parserFlags ccCompilationOptions notNil ifTrue:[
+        cFlags := cFlags , ' ' , parserFlags ccCompilationOptions
+    ].
+
+    "Created: / 07-11-2006 / 12:24:47 / cg"
 ! !
 
 !STCCompilerInterface class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/STCCompilerInterface.st,v 1.4 2006-08-29 17:18:38 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/STCCompilerInterface.st,v 1.5 2006-11-07 11:56:31 cg Exp $'
 ! !
 
 STCCompilerInterface initialize!