BCompiler.st
changeset 599 9eaffb06df33
parent 594 11ae33ac9b34
child 600 81b6ca4882ad
--- a/BCompiler.st	Tue Aug 05 17:28:04 1997 +0200
+++ b/BCompiler.st	Tue Aug 12 10:10:49 1997 +0200
@@ -2326,7 +2326,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
@@ -2344,19 +2344,19 @@
     (mP isDirectory 
     and:[mP isReadable
     and:[mP isWritable]]) ifFalse:[
-	self parseError:('no access to tempDir: ' , mP pathName) position:1.
-	^ #CannotLoad
+        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
     ].
 
     "/ generate a unique name, consisting of my processID and a sequence number
@@ -2364,7 +2364,7 @@
     "/ lifes
 
     SequenceNumber isNil ifTrue:[
-	SequenceNumber := 0.
+        SequenceNumber := 0.
     ].
     SequenceNumber := SequenceNumber + 1.
 
@@ -2373,153 +2373,153 @@
     stFileName := './' , initName , '.st'. 
     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
     ].
 
     [
-	sep := stream class chunkSeparator.
-
-	class := aClass.
-	class isMeta ifTrue:[
-	    class := aClass soleInstance
-	].
-	supers := class allSuperclasses.
-	supers notNil ifTrue:[
-	    supers reverseDo:[:cls|
-		cls ~~ Object ifTrue:[
-		    cls isLoaded ifFalse:[
-			stream close.
-			^ #CannotLoad
-		    ].
-		    cls fileOutDefinitionOn:stream.
-		    stream nextPut:sep; cr.
-		]
-	    ]
-	].
-	class fileOutDefinitionOn:stream.
-	stream nextPut:sep; cr.
-
-	class privateClassesSorted do:[:aPrivateClass |
-	    aPrivateClass fileOutDefinitionOn:stream.
-	    stream nextPut:sep; cr.
-	].
-
-	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 := './' , initName , '.o'. 
-	cFileName := './' , initName , '.c'. 
-	oFileName asFilename delete.
-	cFileName asFilename delete.
-
-	stcFlags := '-commonSymbols +sharedLibCode +newIncremental -E:errorOutput -N' , initName .
-	cFlags := OperatingSystem getOSDefine.
-	cFlags isNil ifTrue:[
-	    cFlags := ''
-	].
-
-	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.
+        sep := stream class chunkSeparator.
+
+        class := aClass.
+        class isMeta ifTrue:[
+            class := aClass soleInstance
+        ].
+        supers := class allSuperclasses.
+        supers notNil ifTrue:[
+            supers reverseDo:[:cls|
+                cls ~~ Object ifTrue:[
+                    cls isLoaded ifFalse:[
+                        stream close.
+                        ^ #CannotLoad
+                    ].
+                    cls fileOutDefinitionOn:stream.
+                    stream nextPut:sep; cr.
+                ]
+            ]
+        ].
+        class fileOutDefinitionOn:stream.
+        stream nextPut:sep; cr.
+
+        class privateClassesSorted do:[:aPrivateClass |
+            aPrivateClass fileOutDefinitionOn:stream.
+            stream nextPut:sep; cr.
+        ].
+
+        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 := './' , initName , '.o'. 
+        cFileName := './' , initName , '.c'. 
+        oFileName asFilename delete.
+        cFileName asFilename delete.
+
+        stcFlags := '-commonSymbols +sharedLibCode +newIncremental -E:errorOutput -N' , initName .
+        cFlags := OperatingSystem getOSDefine.
+        cFlags isNil ifTrue:[
+            cFlags := ''
+        ].
+
+        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.
 
 "/        '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.
+        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.
 "/            'executing: ' infoPrint. command infoPrintCR.
 
-	    self activityNotification:'compiling (cc)'.
-	    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.
-		    errorMessages notNil ifTrue:[
-			errorMessages := errorMessages asStringCollection.
-			errorMessages size > 20 ifTrue:[
-			    errorMessages := (errorMessages copyTo:20) copyWith:'... more messages skipped'
-			].
+            self activityNotification:'compiling (cc)'.
+            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.
+                    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))
@@ -2527,258 +2527,215 @@
     "/                            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
-	    ].
-	    'errorOutput' asFilename remove.
-	    self activityNotification:'compilation failed'.
-	    self parseError:eMsg position:1.
-
-	    OperatingSystem removeFile:oFileName.
-	    OperatingSystem removeFile:'errorOutput'.
-	    self activityNotification:''.
-	    ^ #Error
-	].
-
-	self activityNotification:''.
-	OperatingSystem removeFile:'errorOutput'.
-
-	(ObjectFileLoader notNil 
-	and:[ObjectFileLoader canLoadObjectFiles]) ifFalse:[
-	    self parseError:'no dynamic load configured - cannot load machine code' position:1.
-	    OperatingSystem removeFile:cFileName.
-	    OperatingSystem removeFile:oFileName.
-	    ^ #CannotLoad
-	].
-
-	"
-	 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 , '/' , initName , '.' , (oFileName asFilename suffix).
-	oFileName asFilename moveTo:moduleFileName.
-	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
+            ].
+            'errorOutput' asFilename remove.
+            self activityNotification:'compilation failed'.
+            self parseError:eMsg position:1.
+
+            OperatingSystem removeFile:oFileName.
+            OperatingSystem removeFile:'errorOutput'.
+            self activityNotification:''.
+            ^ #Error
+        ].
+
+        self activityNotification:''.
+        OperatingSystem removeFile:'errorOutput'.
+
+        (ObjectFileLoader notNil 
+        and:[ObjectFileLoader canLoadObjectFiles]) ifFalse:[
+            self parseError:'no dynamic load configured - cannot load machine code' position:1.
+            OperatingSystem removeFile:cFileName.
+            OperatingSystem removeFile:oFileName.
+            ^ #CannotLoad
+        ].
+
+        "
+         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 , '/' , initName , '.' , (oFileName asFilename suffix).
+        oFileName asFilename moveTo:moduleFileName.
+        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
+        ].
     "/    ('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.
-
-		OperatingSystem removeFile:moduleFileName.
-		self parseError:(eMsg , ' - cannot create machine code') position:1.
-		^ #CannotLoad
-	    ]
-	].
+        "/ 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.
+
+                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 [error]: loaded method installed itself elsewhere' errorPrintCR.
-	    ].
-
-	    newMethod source:aString.
-	    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 [error]: loaded method installed itself elsewhere' errorPrintCR.
+            ].
+
+            newMethod source:aString.
+            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.
-	].
+        STCKeepSTIntermediate ifFalse:[
+            OperatingSystem removeFile:stFileName.
+        ].
     ].
 
     "
      |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: 28.12.1995 / 15:52:48 / stefan"
     "Modified: 16.4.1997 / 18:50:54 / cg"
-!
-
-createLoadableObjectFor:baseFileName
-    |osType oFileName soFileName|
-
-    osType := OperatingSystem getOSType.
-    osType = 'irix' ifTrue:[
-	"
-	 link it to a shared object
-	"
-	oFileName := './' , baseFileName , '.o'.
-	soFileName := './' , baseFileName , '.so'. 
-	OperatingSystem removeFile:soFileName.
-	OperatingSystem executeCommand:'ld -shared -all -o ' , soFileName , ' ' , oFileName.
-	OperatingSystem removeFile:oFileName.
-	^ soFileName. 
-    ].
-    osType = 'sys5_4' ifTrue:[
-	"
-	 link it to a shared object
-	"
-	oFileName := './' , baseFileName , '.o'.
-	soFileName := './' , baseFileName , '.so'. 
-	OperatingSystem removeFile:soFileName.
-	OperatingSystem executeCommand:'ld -G -o ' , soFileName , ' ' , oFileName.
-	OperatingSystem removeFile:oFileName.
-	^ soFileName. 
-    ].
-    osType = 'linux' ifTrue:[
-	"
-	 link it to a shared object
-	"
-	oFileName := './' , baseFileName , '.o'.
-	soFileName := './' , baseFileName , '.so'. 
-	OperatingSystem removeFile:soFileName.
-	OperatingSystem executeCommand:'ld -shared -o ' , soFileName , ' ' , oFileName.
-	OperatingSystem removeFile:oFileName.
-	^ soFileName. 
-    ].
-    ^ oFileName
-
-    "Created: 3.1.1996 / 16:04:45 / cg"
-    "Modified: 14.6.1996 / 11:16:46 / stefan"
+    "Modified: 11.8.1997 / 12:25:49 / stefan"
 !
 
 trappingStubMethodFor:aString inCategory:cat
@@ -2822,6 +2779,6 @@
 !ByteCodeCompiler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Attic/BCompiler.st,v 1.120 1997-07-31 22:31:07 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Attic/BCompiler.st,v 1.121 1997-08-12 08:10:49 stefan Exp $'
 ! !
 ByteCodeCompiler initialize!