ByteCodeCompiler.st
changeset 769 cabe7bdb46ec
parent 768 07fcee0355e3
child 772 bd6fcf9e44e4
--- a/ByteCodeCompiler.st	Thu Sep 03 12:02:55 1998 +0200
+++ b/ByteCodeCompiler.st	Thu Sep 03 16:58:48 1998 +0200
@@ -547,11 +547,12 @@
 canCreateMachineCode
     "return true, if compilation to machine code is supported.
      Currently, all SYSV4 and Linux systems do so;
-     REAL/IX, AIX and HPUX do not (due to the need for dynamic loading 
+     REAL/IX and HPUX9.x do not (due to the need for dynamic loading 
      of object files, which is not supported by those).
      MIPS ULTRIX is almost finished, but not yet released.
-
-     However, if no compiler is around (i.e. the demo distribution),
+     (late note - we no longer care for mips-ultrix)
+
+     However, if no stc compiler is around (i.e. the demo distribution),
      there is no chance ..."
 
     ObjectFileLoader isNil ifTrue:[^ false].
@@ -564,7 +565,8 @@
      Compiler canCreateMachineCode     
     "
 
-    "Modified: 13.9.1995 / 15:15:11 / claus"
+    "Modified: / 13.9.1995 / 15:15:11 / claus"
+    "Modified: / 3.9.1998 / 15:56:07 / cg"
 !
 
 ccCompilationOptions
@@ -601,7 +603,16 @@
     "return the path to (name of) the cc command for incremental method compilation"
 
     CC isNil ifTrue:[
-	^ 'cc'
+        OperatingSystem isMSDOSlike ifTrue:[
+            OperatingSystem getCCDefine = '__BORLANDC__' ifTrue:[
+                ^'bcc32'
+            ].
+            ^'cl'
+        ].
+        OperatingSystem getCCDefine = '__GNUC__' ifTrue:[
+            ^'gcc'
+        ].
+        ^ 'cc'
     ].
     ^ CC
 
@@ -610,9 +621,9 @@
      Compiler ccPath:'gcc'     
     "
 
-    "Modified: 13.9.1995 / 15:15:04 / claus"
-    "Created: 5.11.1996 / 17:35:40 / cg"
-    "Modified: 5.11.1996 / 17:37:42 / cg"
+    "Modified: / 13.9.1995 / 15:15:04 / claus"
+    "Created: / 5.11.1996 / 17:35:40 / cg"
+    "Modified: / 3.9.1998 / 15:54:25 / cg"
 !
 
 ccPath:aPathOrCommandName 
@@ -2403,7 +2414,7 @@
 !ByteCodeCompiler methodsFor:'machine code generation'!
 
 compileToMachineCode:aString forClass:aClass inCategory:cat 
-			     notifying:requestor install:install skipIfSame:skipIfSame silent:silent
+                             notifying:requestor 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
@@ -2413,42 +2424,38 @@
     |stFileName stream handle address stcFlags cFlags def
      command oFileName cFileName
      initName newMethod ok status className sep class stcPath ccPath 
-     errorStream errorMessages eMsg m supers mP moduleFileName dummyHandle|
+     errorStream errorMessages eMsg m supers mP moduleFileName 
+     dummyHandle f mapFileName libFileName|
 
     (mP := STCModulePath asFilename) exists ifFalse:[
        mP makeDirectory
     ].
-    (mP isDirectory 
-    and:[mP isReadable
-    and:[mP isWritable]]) ifFalse:[
-	self parseError:('no access to tempDir: ' , mP pathName) position:1.
-	^ #CannotLoad
+    (mP isDirectory and:[mP isReadable and:[mP isWritable]]) ifFalse:[
+        self parseError:('no access to tempDir: ' , mP pathName) position:1.
+        ^ #CannotLoad
     ].
 
     ObjectFileLoader isNil ifTrue:[^ #CannotLoad].
     STCCompilation == #never ifTrue:[^ #CannotLoad].
     (stcPath := self class incrementalStcPath) isNil ifTrue:[
-	self parseError:'no stc compiler available - cannot create machine code' position:1.
-	^ #CannotLoad
+        self parseError:'no stc compiler available - cannot create machine code' position:1.
+        ^ #CannotLoad
     ].
     (ccPath := self class ccPath) isNil ifTrue:[
-	self parseError:'no cc compiler available - cannot create machine code' position:1.
-	^ #CannotLoad
+        self parseError:'no cc compiler available - cannot create machine code' position:1.
+        ^ #CannotLoad
     ].
 
-    (ObjectFileLoader notNil 
-    and:[ObjectFileLoader canLoadObjectFiles]) ifFalse:[
-	self parseError:'no dynamic loader configured - cannot create machine code' position:1.
-	^ #CannotLoad
+    (ObjectFileLoader notNil and:[ObjectFileLoader canLoadObjectFiles]) ifFalse:[
+        self parseError:'no dynamic loader configured - cannot create machine code' position:1.
+        ^ #CannotLoad
     ].
 
     "/ 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 isNil ifTrue:[
-	SequenceNumber := 0.
-    ].
+    SequenceNumber isNil ifTrue:[SequenceNumber := 0].
     SequenceNumber := SequenceNumber + 1.
 
     initName := 'm_' , OperatingSystem getProcessId printString, '_' , SequenceNumber printString.
@@ -2456,185 +2463,182 @@
     stFileName := (Filename currentDirectory construct:(initName , '.st')) name. 
     stream := stFileName asFilename writeStream.
     stream isNil ifTrue:[
-	self parseError:'cannot create temporary sourcefile for compilation'.
-	^ #CannotLoad
+        self parseError:'cannot create temporary sourcefile for compilation'.
+        ^ #CannotLoad
     ].
 
     [
-	|definedClasses|
-
-	definedClasses := IdentitySet new.
-
-	sep := stream class chunkSeparator.
-
-	class := aClass.
-	class isMeta ifTrue:[
-	    class := aClass soleInstance
-	].
-	supers := class allSuperclasses.
-	supers notNil ifTrue:[
-	    supers reverseDo:[:cls|
-		true "cls ~~ Object" ifTrue:[
-		    cls isLoaded ifFalse:[
-			stream close.
-			^ #CannotLoad
-		    ].
-		    cls fileOutDefinitionOn:stream.
-		    stream nextPut:sep; cr.
-		    definedClasses add:cls.
-		]
-	    ]
-	].
-	class fileOutDefinitionOn:stream.
-	stream nextPut:sep; cr.
-	definedClasses add:class.
-
-	class privateClassesSorted do:[:aPrivateClass |
-	    supers := aPrivateClass allSuperclasses.
-	    supers notNil ifTrue:[
-		supers reverseDo:[:cls|
-		    (definedClasses includes:cls) ifFalse:[
-			true "cls ~~ Object" ifTrue:[
-			    cls isLoaded ifFalse:[
-				stream close.
-				^ #CannotLoad
-			    ].
-			    cls fileOutDefinitionOn:stream.
-			    stream nextPut:sep; cr.
-			    definedClasses add:cls.
-			]
-		    ]
-		]
-	    ].
-	    (definedClasses includes:aPrivateClass) ifFalse:[
-		aPrivateClass fileOutDefinitionOn:stream.
-		stream nextPut:sep; cr.
-		definedClasses add:aPrivateClass.
-	    ]
-	].
-
-	class fileOutPrimitiveDefinitionsOn:stream.
-
-	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. 
-	oFileName asFilename delete.
-	cFileName asFilename delete.
-
-	stcFlags := '-commonSymbols +sharedLibCode +newIncremental -E:errorOutput -N' , initName .
-	cFlags := OperatingSystem getOSDefine.
-	cFlags isNil ifTrue:[
-	    cFlags := ''
-	].
-	(def := OperatingSystem getCPUDefine) notNil ifTrue:[
-	    cFlags := cFlags , ' ' , def
-	].
-
-	STCCompilationDefines notNil ifTrue:[
-	    cFlags := cFlags , ' ' , STCCompilationDefines
-	].
-	STCCompilationIncludes notNil ifTrue:[
-	    stcFlags := STCCompilationIncludes , ' ' , stcFlags.
-	    cFlags := cFlags , ' ' , STCCompilationIncludes.
-	].
-	STCCompilationOptions notNil ifTrue:[
-	    stcFlags := STCCompilationOptions , ' ' , stcFlags
-	].
-	CCCompilationOptions notNil ifTrue:[
-	    cFlags := cFlags , ' ' , CCCompilationOptions
-	].
-
-	command := stcPath , ' ' , stcFlags , ' -C ' , stFileName.
-
-	Verbose == true ifTrue:[
-	    'executing: ' infoPrint. command infoPrintCR.
-	].
-	errorStream := 'errorOutput' asFilename writeStream.
-
-	self 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 it failed - but c-file is there ...' infoPrintCR.
-		ok := true
-	    ]
-	] ifFalse:[
-	    ok := false
-	].
-
-	ok ifTrue:[
-	    "/ now compile to machine code
-
-	    command := ccPath , ' ' , cFlags , ' -c ' , cFileName.
-	    Verbose == true ifTrue:[
-		'executing: ' infoPrint. command infoPrintCR.
-	    ].
-	    self 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 it failed - but o-file is there ...' infoPrintCR.
-		    ok := true
-		]
-	    ] ifFalse:[
-		ok := false
-	    ].
-
-	    "for debugging - leave c intermediate"
-	    STCKeepCIntermediate == true ifFalse:[
-		OperatingSystem removeFile:cFileName.
-	    ].
-	].
-
-	ok ifFalse:[
-	    (status notNil and:[status couldNotExecute]) ifTrue:[
-		eMsg := 'oops, no STC - cannot create machine code'
-	    ] ifFalse:[
-		errorStream := 'errorOutput' asFilename readStream.
-		errorStream notNil ifTrue:[
-		    errorMessages := errorStream contents.
-		    errorStream close.
-		    errorMessages notNil ifTrue:[
-			errorMessages := errorMessages asStringCollection.
-			errorMessages size > 20 ifTrue:[
-			    errorMessages := (errorMessages copyTo:20) copyWith:'... more messages skipped'
-			].
+        |definedClasses|
+
+        definedClasses := IdentitySet new.
+
+        sep := stream class chunkSeparator.
+
+        class := aClass.
+        class isMeta ifTrue:[
+            class := aClass soleInstance
+        ].
+        supers := class allSuperclasses.
+        supers notNil ifTrue:[
+            supers reverseDo:[:cls|
+                true "cls ~~ Object" ifTrue:[
+                    cls isLoaded ifFalse:[
+                        stream close.
+                        ^ #CannotLoad
+                    ].
+                    cls fileOutDefinitionOn:stream.
+                    stream nextPut:sep; cr.
+                    definedClasses add:cls.
+                ]
+            ]
+        ].
+        class fileOutDefinitionOn:stream.
+        stream nextPut:sep; cr.
+        definedClasses add:class.
+
+        class privateClassesSorted do:[:aPrivateClass |
+            supers := aPrivateClass allSuperclasses.
+            supers notNil ifTrue:[
+                supers reverseDo:[:cls|
+                    (definedClasses includes:cls) ifFalse:[
+                        true "cls ~~ Object" ifTrue:[
+                            cls isLoaded ifFalse:[
+                                stream close.
+                                ^ #CannotLoad
+                            ].
+                            cls fileOutDefinitionOn:stream.
+                            stream nextPut:sep; cr.
+                            definedClasses add:cls.
+                        ]
+                    ]
+                ]
+            ].
+            (definedClasses includes:aPrivateClass) ifFalse:[
+                aPrivateClass fileOutDefinitionOn:stream.
+                stream nextPut:sep; cr.
+                definedClasses add:aPrivateClass.
+            ]
+        ].
+
+        class fileOutPrimitiveDefinitionsOn:stream.
+
+        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 .
+        cFlags := OperatingSystem getOSDefine.
+        cFlags isNil ifTrue:[
+            cFlags := ''
+        ].
+        (def := OperatingSystem getCPUDefine) notNil ifTrue:[
+            cFlags := cFlags , ' ' , def
+        ].
+
+        STCCompilationDefines notNil ifTrue:[
+            cFlags := cFlags , ' ' , STCCompilationDefines
+        ].
+        STCCompilationIncludes notNil ifTrue:[
+            stcFlags := STCCompilationIncludes , ' ' , stcFlags.
+            cFlags := cFlags , ' ' , STCCompilationIncludes.
+        ].
+        STCCompilationOptions notNil ifTrue:[
+            stcFlags := STCCompilationOptions , ' ' , stcFlags
+        ].
+        CCCompilationOptions notNil ifTrue:[
+            cFlags := cFlags , ' ' , CCCompilationOptions
+        ].
+
+        command := stcPath , ' ' , stcFlags , ' -C ' , stFileName.
+
+        Verbose == true ifTrue:[
+            'executing: ' infoPrint. command infoPrintCR.
+        ].
+        errorStream := 'errorOutput' asFilename writeStream.
+
+        self 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 it failed - but c-file is there ...' infoPrintCR.
+                ok := true
+            ]
+        ] ifFalse:[
+            ok := false
+        ].
+
+        ok ifTrue:[
+            "/ now compile to machine code
+
+            command := ccPath , ' ' , cFlags , ' -c ' , cFileName.
+            Verbose == true ifTrue:[
+                'executing: ' infoPrint. command infoPrintCR.
+            ].
+            self 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 it failed - but o-file is there ...' infoPrintCR.
+                    ok := true
+                ]
+            ] ifFalse:[
+                ok := false
+            ].
+        ].
+
+        ok ifFalse:[
+            (status notNil and:[status couldNotExecute]) ifTrue:[
+                eMsg := 'oops, no STC - cannot create machine code'
+            ] ifFalse:[
+                errorStream := 'errorOutput' asFilename readStream.
+                errorStream notNil ifTrue:[
+                    errorMessages := errorStream contents.
+                    errorStream close.
+                    errorMessages notNil ifTrue:[
+                        errorMessages := errorMessages asStringCollection.
+                        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))
@@ -2642,219 +2646,218 @@
     "/                            line
     "/                        ]
     "/                      ].
-			errorMessages := errorMessages asString
-		    ].
-		].
-		errorMessages isNil ifTrue:[
-		    errorMessages := ''
-		].
-		errorMessages isEmpty ifTrue:[
-		    eMsg := 'STC / CC error during compilation:\\unspecified error'
-		] ifFalse:[
-		    eMsg := 'STC / CC error during compilation:\\',errorMessages
-		].
-		eMsg := eMsg withCRs
-	    ].
-	    OperatingSystem removeFile:'errorOutput'.
-	    self activityNotification:'compilation failed'.
-	    self parseError:eMsg position:1.
-
-	    STCKeepOIntermediate == true ifFalse:[
-		OperatingSystem removeFile:oFileName.
-	    ].
-	    self activityNotification:''.
-	    ^ #Error
-	].
-
-	self activityNotification:''.
-	OperatingSystem removeFile:'errorOutput'.
-
-	"
-	 if required, make a shared or otherwise loadable object file for it
-	"
-	self activityNotification:'linking'.
-	oFileName := ObjectFileLoader createLoadableObjectFor:initName.
-	oFileName isNil ifTrue:[
-	    "/ something went wrong
-	    self parseError:(ObjectFileLoader lastError) position:1.
-	    ^ #CannotLoad
-	].
-
-	oFileName asFilename exists ifFalse:[
-	    OperatingSystem removeFile:oFileName.
-	    self parseError:'link failed - cannot create machine code' position:1.
-	    ^ #CannotLoad
-	].
-
-	"
-	 move it into the modules directory
-	"
-
-	moduleFileName := (STCModulePath asFilename construct:(initName , '.' , (oFileName asFilename suffix))) name.
-	oFileName asFilename moveTo:moduleFileName.
-	(moduleFileName asFilename exists 
-	and:[moduleFileName asFilename isReadable]) ifFalse:[
-	    OperatingSystem removeFile:oFileName.
-	    self parseError:'link failed - cannot move shared library module to ''modules'' directory' position:1.
-	    ^ #CannotLoad
-	].
-	oFileName := moduleFileName.
-
-	"
-	 load the objectfile
-	"
-	self activityNotification:'loading'.
-	handle := ObjectFileLoader loadDynamicObject:moduleFileName.
-	handle isNil ifTrue:[
-	    OperatingSystem removeFile:moduleFileName.
-	    self parseError:'dynamic load failed - cannot create machine code' position:1.
-	    ^ #CannotLoad
-	].
+                        errorMessages := errorMessages asString
+                    ].
+                ].
+                errorMessages isNil ifTrue:[
+                    errorMessages := ''
+                ].
+                errorMessages isEmpty ifTrue:[
+                    eMsg := 'STC / CC error during compilation:\\unspecified error'
+                ] ifFalse:[
+                    eMsg := 'STC / CC error during compilation:\\',errorMessages
+                ].
+                eMsg := eMsg withCRs
+            ].
+            self activityNotification:'compilation failed'.
+            self parseError:eMsg position:1.
+
+            self activityNotification:''.
+            ^ #Error
+        ].
+
+        self activityNotification:''.
+        OperatingSystem removeFile:'errorOutput'.
+
+        "
+         if required, make a shared or otherwise loadable object file for it
+        "
+        self activityNotification:'linking'.
+
+        oFileName := ObjectFileLoader createLoadableObjectFor:initName.
+        oFileName isNil ifTrue:[
+            "/ something went wrong
+            self parseError:(ObjectFileLoader lastError) position:1.
+            ^ #CannotLoad
+        ].
+        oFileName asFilename exists ifFalse:[
+            self parseError:'link failed - cannot create machine code' position:1.
+            ^ #CannotLoad
+        ].
+
+        "
+         move it into the modules directory
+        "
+        moduleFileName := (STCModulePath asFilename construct:(initName , '.' , (oFileName asFilename suffix))) name.
+        oFileName asFilename moveTo:moduleFileName.
+        (moduleFileName asFilename exists 
+        and:[moduleFileName asFilename isReadable]) ifFalse:[
+            self parseError:'link failed - cannot move shared library module to ''modules'' directory' position:1.
+            ^ #CannotLoad
+        ].
+
+        "
+         load the objectfile
+        "
+        self activityNotification:'loading'.
+        handle := ObjectFileLoader loadDynamicObject:moduleFileName.
+        handle isNil ifTrue:[
+            OperatingSystem removeFile:moduleFileName.
+            self parseError:'dynamic load failed - cannot create machine code' position:1.
+            ^ #CannotLoad
+        ].
     "/    ('handle is ' , handle printString) infoPrintCR.
 
-	"/ try libs to resolve symbols.
-	address := ObjectFileLoader getFunction:'__' , initName , '_Init' from:handle.
-	address isNil ifTrue:[
-	    address := ObjectFileLoader getFunction:'_' , initName , '_Init' from:handle.
-	    address isNil ifTrue:[
-		(ObjectFileLoader hasUndefinedSymbolsIn:handle) ifTrue:[
-		    ObjectFileLoader searchedLibraries do:[:libName |
-			(ObjectFileLoader hasUndefinedSymbolsIn:handle) ifTrue:[
-			    Transcript showCR:'   ... trying ' , libName , ' to resolve undefined symbols ...'.
-			    dummyHandle := Array new:4.
-			    dummyHandle := ObjectFileLoader primLoadDynamicObject:libName into:dummyHandle.
-			    dummyHandle isNil ifTrue:[
-				Transcript showCR:'   ... load of library ' , libName , ' failed.'.
-			    ]
-			]
-		    ].
-		    (ObjectFileLoader hasUndefinedSymbolsIn:handle) isNil ifTrue:[
-			Transcript showCR:('LOADER: still undefined symbols in ',initName,'.').
-		    ].
-		].
-
-	    ]
-	].
-
-	address := ObjectFileLoader getFunction:'__' , initName , '_Init' from:handle.
-	address isNil ifTrue:[
-	    address := ObjectFileLoader getFunction:'_' , initName , '_Init' from:handle.
-	    address isNil ifTrue:[
-		(ObjectFileLoader getListOfUndefinedSymbolsFrom:handle) size > 0 ifTrue:[
-		    ObjectFileLoader listUndefinedSymbolsIn:handle.
-		    eMsg := 'undefined symbols in primitive code'.
-		] ifFalse:[
-		    eMsg := initName , '_Init() lookup failed'
-		].
-
-		ObjectFileLoader unloadDynamicObject:handle.
+        "/ try libs to resolve symbols.
+        (ObjectFileLoader hasUndefinedSymbolsIn:handle) ifTrue:[
+            ObjectFileLoader searchedLibraries do:[:libName |
+                (ObjectFileLoader hasUndefinedSymbolsIn:handle) ifTrue:[
+                    Transcript showCR:'   ... trying ' , libName , ' to resolve undefined symbols ...'.
+                    dummyHandle := Array new:4.
+                    dummyHandle := ObjectFileLoader primLoadDynamicObject:libName into:dummyHandle.
+                    dummyHandle isNil ifTrue:[
+                        Transcript showCR:'   ... load of library ' , libName , ' failed.'.
+                    ]
+                ]
+            ].
+            (ObjectFileLoader hasUndefinedSymbolsIn:handle) isNil ifTrue:[
+                Transcript showCR:('LOADER: still undefined symbols in ',initName,'.').
+            ].
+        ].
+
+        address := ObjectFileLoader getFunction:'__' , initName , '_Init' from:handle.
+        address isNil ifTrue:[
+            address := ObjectFileLoader getFunction:'_' , initName , '_Init' from:handle.
+            address isNil ifTrue:[
+                address := ObjectFileLoader getFunction:initName , '_Init' from:handle.
+                address isNil ifTrue:[
+                    (ObjectFileLoader getListOfUndefinedSymbolsFrom:handle) size > 0 ifTrue:[
+                        ObjectFileLoader listUndefinedSymbolsIn:handle.
+                        eMsg := 'undefined symbols in primitive code'.
+                    ] ifFalse:[
+                        eMsg := initName , '_Init() lookup failed'
+                    ].
+
+                    ObjectFileLoader unloadDynamicObject:handle.
 
 "/                OperatingSystem getSystemType = 'osf' ifTrue:[
 "/                   OperatingSystem executeCommand:('nm -u ' , moduleFileName)
 "/                ].
 
-		OperatingSystem removeFile:moduleFileName.
-		self parseError:(eMsg , ' - cannot create machine code') position:1.
-		^ #CannotLoad
-	    ]
-	].
+"/                    OperatingSystem removeFile:moduleFileName.
+                    self parseError:(eMsg , ' - cannot create machine code') position:1.
+                    ^ #CannotLoad
+                ]
+            ]
+        ].
 
     "/    ('init at ' , address printString) infoPrintCR.
 
-	m := ObjectFileLoader 
-	    callInitFunctionAt:address 
-	    specialInit:true
-	    forceOld:true 
-	    interruptable:false
-	    argument:2
-	    identifyAs:handle
-	    returnsObject:true.
-
-	"
-	 did it work ?
-	"
-	newMethod := aClass compiledMethodAt:selector.
-	newMethod notNil ifTrue:[
-	    m ~~ newMethod ifTrue:[
-		'Compiler [warning]: loaded method installed itself in another class' errorPrintCR.
-	    ].
-
-	    newMethod source:aString string.
-	    newMethod package:(Class packageQuerySignal raise).
+        m := ObjectFileLoader 
+            callInitFunctionAt:address 
+            specialInit:true
+            forceOld:true 
+            interruptable:false
+            argument:2
+            identifyAs:handle
+            returnsObject:true.
+
+        "
+         did it work ?
+        "
+        newMethod := aClass compiledMethodAt:selector.
+        newMethod notNil ifTrue:[
+            m ~~ newMethod ifTrue:[
+                'Compiler [warning]: loaded method installed itself in another class' errorPrintCR.
+            ].
+
+            newMethod source:aString string.
+            newMethod package:(Class packageQuerySignal raise).
 "/            Project notNil ifTrue:[
 "/                newMethod package:(Project currentPackageName)
 "/            ].
 
     "/        aClass updateRevisionString.
-	    aClass addChangeRecordForMethod:newMethod.
-	    (silent or:[Smalltalk silentLoading == true]) ifFalse:[
-		Transcript showCR:('    compiled: ', className,' ',selector,' - machine code')
-	    ].
-	    ObjectMemory flushCaches.
-
-	    handle method:newMethod.
-
-	    "/ check for obsolete loaded objects and unload them
-
-	    ObjectFileLoader loadedObjectHandlesDo:[:anotherHandle |
-		anotherHandle isMethodHandle ifTrue:[
-		    anotherHandle method isNil ifTrue:[
-			ObjectFileLoader unloadObjectFile:anotherHandle pathName.
-			OperatingSystem removeFile:anotherHandle pathName.
-		    ]
-		]
-	    ].
-	    ^ newMethod.
-	].
-
-	OperatingSystem removeFile:moduleFileName.
-	self parseError:'dynamic load failed' position:1.
-	^ #CannotLoad
+            aClass addChangeRecordForMethod:newMethod.
+            (silent or:[Smalltalk silentLoading == true]) ifFalse:[
+                Transcript showCR:('    compiled: ', className,' ',selector,' - machine code')
+            ].
+            ObjectMemory flushCaches.
+
+            handle method:newMethod.
+
+            "/ check for obsolete loaded objects and unload them
+
+            ObjectFileLoader loadedObjectHandlesDo:[:anotherHandle |
+                anotherHandle isMethodHandle ifTrue:[
+                    anotherHandle method isNil ifTrue:[
+                        ObjectFileLoader unloadObjectFile:anotherHandle pathName.
+                        OperatingSystem removeFile:anotherHandle pathName.
+                    ]
+                ]
+            ].
+            ^ newMethod.
+        ].
+
+        OperatingSystem removeFile:moduleFileName.
+        self parseError:'dynamic load failed' position:1.
+        ^ #CannotLoad
     ] valueNowOrOnUnwindDo:[
-	STCKeepSTIntermediate ifFalse:[
-	    OperatingSystem removeFile:stFileName.
-	].
+        OperatingSystem removeFile:'errorOutput'.
+        STCKeepSTIntermediate ifFalse:[
+            OperatingSystem removeFile:stFileName.
+        ].
+        STCKeepOIntermediate == true ifFalse:[
+            (oFileName notNil and:[oFileName asFilename exists]) ifTrue:[oFileName asFilename delete].
+        ].
+        STCKeepCIntermediate == true ifFalse:[
+            (cFileName notNil and:[cFileName asFilename exists]) ifTrue:[cFileName asFilename delete].
+        ].
+        OperatingSystem isMSDOSlike ifTrue:[
+"/            (mapFileName notNil and:[mapFileName asFilename exists]) ifTrue:[mapFileName asFilename delete].
+"/            (libFileName notNil and:[libFileName asFilename exists]) ifTrue:[libFileName asFilename delete].
+        ].
     ].
 
     "
      |m|
 
      Object subclass:#Test
-	    instanceVariableNames:''
-	    classVariableNames:''
-	    poolDictionaries:''
-	    category:'tests'.
+            instanceVariableNames:''
+            classVariableNames:''
+            poolDictionaries:''
+            category:'tests'.
      m := ByteCodeCompiler
-	    compile:'foo ^ ''hello'''
-	    forClass:Test
-	    inCategory:'tests'
-	    notifying:nil
-	    install:false
-	    skipIfSame:false.
+            compile:'foo ^ ''hello'''
+            forClass:Test
+            inCategory:'tests'
+            notifying:nil
+            install:false
+            skipIfSame:false.
      m inspect
     "
     "
      |m|
 
      Object subclass:#Test
-	    instanceVariableNames:''
-	    classVariableNames:''
-	    poolDictionaries:''
-	    category:'tests'.
+            instanceVariableNames:''
+            classVariableNames:''
+            poolDictionaries:''
+            category:'tests'.
      m := ByteCodeCompiler
-	    compileToMachineCode:'foo %{ RETURN (_MKSMALLINT(1)); %}'
-	    forClass:Test
-	    inCategory:'tests'
-	    notifying:nil
-	    install:false
-	    skipIfSame:false
-	    silent:false.
+            compileToMachineCode:'foo %{ RETURN (_MKSMALLINT(1)); %}'
+            forClass:Test
+            inCategory:'tests'
+            notifying:nil
+            install:false
+            skipIfSame:false
+            silent:false.
      m inspect
     "
 
     "Modified: / 14.9.1995 / 22:33:04 / claus"
     "Modified: / 11.8.1997 / 12:25:49 / stefan"
-    "Modified: / 3.8.1998 / 16:52:42 / cg"
+    "Modified: / 3.9.1998 / 16:05:20 / cg"
 !
 
 trappingStubMethodFor:aString inCategory:cat
@@ -2898,6 +2901,6 @@
 !ByteCodeCompiler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/ByteCodeCompiler.st,v 1.141 1998-09-03 10:02:55 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/ByteCodeCompiler.st,v 1.142 1998-09-03 14:58:48 cg Exp $'
 ! !
 ByteCodeCompiler initialize!