ByteCodeCompiler.st
changeset 172 85ad12831217
parent 162 2349ee7039ce
child 174 3be731572be7
--- a/ByteCodeCompiler.st	Wed Dec 13 20:43:56 1995 +0100
+++ b/ByteCodeCompiler.st	Wed Dec 13 20:45:43 1995 +0100
@@ -11,13 +11,13 @@
 "
 
 Parser subclass:#ByteCodeCompiler
-	 instanceVariableNames:'codeBytes codeIndex litArray stackDelta extra lineno
-                maxStackDepth relocList'
-	 classVariableNames:'JumpToAbsJump SequenceNumber STCCompilationDefines
-                STCCompilationIncludes STCCompilationOptions STCCompilation
-                KeepSource STCKeepCIntermediate'
-	 poolDictionaries:''
-	 category:'System-Compiler'
+	instanceVariableNames:'codeBytes codeIndex litArray stackDelta extra lineno
+		maxStackDepth relocList'
+	classVariableNames:'JumpToAbsJump SequenceNumber STCCompilationDefines
+		STCCompilationIncludes STCCompilationOptions STCCompilation
+		KeepSource STCKeepCIntermediate'
+	poolDictionaries:''
+	category:'System-Compiler'
 !
 
 !ByteCodeCompiler class methodsFor:'documentation'!
@@ -142,7 +142,7 @@
 !
 
 compile:aString forClass:aClass inCategory:cat notifying:requestor
-		 install:install skipIfSame:skipIfSame silent:silent
+                 install:install skipIfSame:skipIfSame silent:silent
 
     "the basic workhorse method for compiling:
      compile a source-string for a method in classToCompileFor.
@@ -157,7 +157,7 @@
      The argument, silent controls if errors are to be reported."
 
     |compiler newMethod tree lits symbolicCodeArray oldMethod lazy silencio 
-     sourceFile sourceStream newSource primNr pos sel|
+     sourceFile sourceStream newSource primNr pos sel keptOldCode msg answer|
 
     aString isNil ifTrue:[^ nil].
     silencio := silent or:[Smalltalk silentLoading == true].
@@ -172,59 +172,52 @@
     compiler notifying:requestor.
     silent ifTrue:[
 "/        compiler ignoreErrors.
-	compiler ignoreWarnings
+        compiler ignoreWarnings
     ].
     compiler nextToken.
     (compiler parseMethodSpec == #Error) ifTrue:[
-	tree := #Error
+        compiler parseError:'syntax error in method specification'.
+        tree := #Error
     ] ifFalse:[
-	"check if same source"
-	(skipIfSame and:[(sel := compiler selector) notNil]) ifTrue:[
-	    oldMethod := aClass compiledMethodAt:sel.
-	    oldMethod notNil ifTrue:[
-		oldMethod source = aString ifTrue:[
-		    oldMethod isInvalid ifFalse:[
-			silencio ifFalse:[
-			    Transcript showCr:('    unchanged: ',aClass name,' ',compiler selector)
-			].
-			"
-			 same. however, category may be different
-			"
-			(cat notNil and:[cat ~~ oldMethod category]) ifTrue:[
-			    oldMethod category:cat.
-			    oldMethod changed:#category.    
+        "check if same source"
+        (skipIfSame and:[(sel := compiler selector) notNil]) ifTrue:[
+            oldMethod := aClass compiledMethodAt:sel.
+            oldMethod notNil ifTrue:[
+                oldMethod source = aString ifTrue:[
+                    oldMethod isInvalid ifFalse:[
+                        silencio ifFalse:[
+                            Transcript showCr:('    unchanged: ',aClass name,' ',compiler selector)
+                        ].
+                        "
+                         same. however, category may be different
+                        "
+                        (cat notNil and:[cat ~~ oldMethod category]) ifTrue:[
+                            oldMethod category:cat.
+                            oldMethod changed:#category.    
 "/                            aClass updateRevisionString.
-			    aClass addChangeRecordForMethodCategory:oldMethod category:cat.
-			].
-			^ oldMethod
-		    ]
-		]
-	    ]
-	].
-	lazy ifFalse:[
-	    tree := compiler parseMethodBody.
-	    compiler tree:tree.
-	]
+                            aClass addChangeRecordForMethodCategory:oldMethod category:cat.
+                        ].
+                        ^ oldMethod
+                    ]
+                ]
+            ]
+        ].
+        lazy ifFalse:[
+            tree := compiler parseMethodBody.
+            compiler tree:tree.
+        ]
     ].
 
     sel := compiler selector.
     (compiler errorFlag or:[tree == #Error]) ifTrue:[
-"/        compiler parseError:'syntax error'.
-	Transcript show:'    '.
-	aClass notNil ifTrue:[
-	    Transcript show:aClass name , '>>'
-	].
-	sel notNil ifTrue:[
-	    Transcript show:(sel)
-	].
-	Transcript showCr:' -> Error'.
-	^ #Error
+        compiler showErrorMessageForClass:aClass.
+        ^ #Error
     ].
 
     "if no error and also no selector ..."
      sel isNil ifTrue:[
-	"... it was just a comment or other empty stuff"
-	^ nil
+        "... it was just a comment or other empty stuff"
+        ^ nil
     ].
 
     "
@@ -233,27 +226,69 @@
     (compiler hasNonOptionalPrimitiveCode 
     or:[(compiler hasPrimitiveCode and:[self canCreateMachineCode])
     or:[STCCompilation == #always and:[sel  ~~ #doIt]]]) ifTrue:[
-	newMethod := compiler 
-			compileToMachineCode:aString 
-			forClass:aClass 
-			inCategory:cat 
-			notifying:requestor
-			install:install 
-			skipIfSame:skipIfSame 
-			silent:silent.
+        newMethod := compiler 
+                        compileToMachineCode:aString 
+                        forClass:aClass 
+                        inCategory:cat 
+                        notifying:requestor
+                        install:install 
+                        skipIfSame:skipIfSame 
+                        silent:silent.
+
+        newMethod == #Error ifTrue:[
+            compiler showErrorMessageForClass:aClass.
+            ^ #Error
+        ].
+
+        (newMethod == #CannotLoad) ifTrue:[
+            newMethod := compiler trappingStubMethodFor:aString inCategory:cat.
+
+            keptOldCode := false.
+            install ifTrue:[
+                "/
+                "/ be very careful with existing methods
+                "/ (otherwise, you could easily make your system unusable in systems which cannot load)
+                "/
+                sel notNil ifTrue:[
+                    oldMethod := aClass compiledMethodAt:sel 
+                ].
+                (oldMethod notNil and:[oldMethod code ~= newMethod code]) ifTrue:[
+                    answer := Dialog
+                                 confirm:'installation of binary code is not possible or disabled.
 
-	newMethod ==#Error ifTrue:[
-	    newMethod := compiler trappingStubMethodFor:aString inCategory:cat.
-	    install ifTrue:[
-		aClass addSelector:sel withMethod:newMethod
-	    ].
-	    Transcript show:'*** '.
-	    sel notNil ifTrue:[
-		Transcript show:(sel ,' ')
-	    ].
-	    Transcript showCr:'not compiled to machine code - created a stub instead.'.
-	].
-	^ newMethod
+Shall I use the old methods functionality
+or instead create a dummy trap method for it ?
+
+Hint:
+  if that method is needed by the system, you better leave the
+  original functionality in the system.
+
+Close this warnBox to abort the compilation.
+'
+                                 yesLabel:'trap code'
+                                 noLabel:'keep old'.
+                    answer isNil ifTrue:[
+                        ^ #Error
+                    ].
+                    answer == false ifTrue:[
+                        newMethod code:(oldMethod code).
+                        keptOldCode := true.
+                    ].
+                ].
+                aClass addSelector:sel withMethod:newMethod
+            ].
+            Transcript show:'*** '.
+            sel notNil ifTrue:[
+                Transcript show:(sel ,' ')
+            ].
+            keptOldCode ifTrue:[
+                msg := 'not really compiled - method still shows previous behavior'.
+            ] ifFalse:[
+                msg := 'not compiled to machine code - created a stub instead.'.
+            ].
+            Transcript showCr:msg.
+        ].
+        ^ newMethod
     ].
 
     "
@@ -262,56 +297,56 @@
      compile itself when first called.
     "
     lazy ifTrue:[
-	newMethod := LazyMethod new.
-	KeepSource == false ifTrue:[
-	    sourceFile := ObjectMemory nameForSources.
-	    sourceStream := sourceFile asFilename appendingWriteStream.
-	].
-	sourceStream isNil ifTrue:[
-	    newMethod source:aString.
-	] ifFalse:[
-	    sourceStream setToEnd.
-	    pos := sourceStream position.
-	    sourceStream nextChunkPut:aString.
-	    sourceStream close.
-	    newMethod sourceFilename:sourceFile position:pos.
-	].
-	newMethod category:cat.
-	Project notNil ifTrue:[
-	    newMethod package:(Project currentPackageName)
-	].
+        newMethod := LazyMethod new.
+        KeepSource == false ifTrue:[
+            sourceFile := ObjectMemory nameForSources.
+            sourceStream := sourceFile asFilename appendingWriteStream.
+        ].
+        sourceStream isNil ifTrue:[
+            newMethod source:aString.
+        ] ifFalse:[
+            sourceStream setToEnd.
+            pos := sourceStream position.
+            sourceStream nextChunkPut:aString.
+            sourceStream close.
+            newMethod sourceFilename:sourceFile position:pos.
+        ].
+        newMethod category:cat.
+        Project notNil ifTrue:[
+            newMethod package:(Project currentPackageName)
+        ].
 
-	aClass addSelector:sel withLazyMethod:newMethod.
-	^ newMethod
+        aClass addSelector:sel withLazyMethod:newMethod.
+        ^ newMethod
     ].
 
     (primNr := compiler primitiveNumber) isNil ifTrue:[
-	"
-	 produce symbolic code first
-	"
-	symbolicCodeArray := compiler genSymbolicCode.
+        "
+         produce symbolic code first
+        "
+        symbolicCodeArray := compiler genSymbolicCode.
 
-	(symbolicCodeArray == #Error) ifTrue:[
-	    Transcript show:'    '.
-	    sel notNil ifTrue:[
-		Transcript show:(sel ,' ')
-	    ].
-	    Transcript showCr:'translation error'.
-	    ^ #Error
-	].
+        (symbolicCodeArray == #Error) ifTrue:[
+            Transcript show:'    '.
+            sel notNil ifTrue:[
+                Transcript show:(sel ,' ')
+            ].
+            Transcript showCr:'translation error'.
+            ^ #Error
+        ].
 
-	"
-	 take this, producing bytecode 
-	 (someone willin' to make machine code :-)
-	"
-	((compiler genByteCodeFrom:symbolicCodeArray) == #Error) ifTrue:[
-	    Transcript show:'    '.
-	     sel notNil ifTrue:[
-		Transcript show:(sel ,' ')
-	    ].
-	    Transcript showCr:'relocation error - must be simplified'.
-	    ^ #Error
-	].
+        "
+         take this, producing bytecode 
+         (someone willin' to make machine code :-)
+        "
+        ((compiler genByteCodeFrom:symbolicCodeArray) == #Error) ifTrue:[
+            Transcript show:'    '.
+             sel notNil ifTrue:[
+                Transcript show:(sel ,' ')
+            ].
+            Transcript showCr:'relocation error - must be simplified'.
+            ^ #Error
+        ].
     ].
 
     "
@@ -320,14 +355,14 @@
     newMethod := Method new.
     lits := compiler literalArray.
     lits notNil ifTrue:[
-	"literals MUST be an array - not just any Collection"
-	lits := Array withAll:lits.
-	newMethod literals:lits
+        "literals MUST be an array - not just any Collection"
+        lits := Array withAll:lits.
+        newMethod literals:lits
     ].
     primNr notNil ifTrue:[
-	newMethod code:(compiler checkForPrimitiveCode:primNr).
+        newMethod code:(compiler checkForPrimitiveCode:primNr).
     ] ifFalse:[
-	newMethod byteCode:(compiler code).
+        newMethod byteCode:(compiler code).
     ].
     newMethod numberOfMethodVars:(compiler numberOfMethodVars).
     newMethod numberOfMethodArgs:(compiler numberOfMethodArgs).
@@ -337,26 +372,27 @@
      if there where any corrections, install the updated source
     "
     (newSource := compiler correctedSource) notNil ifTrue:[
-	newMethod source:newSource 
+        newMethod source:newSource 
     ] ifFalse:[
-	newMethod source:aString.
+        newMethod source:aString.
     ].
     newMethod category:cat.
     Project notNil ifTrue:[
-	newMethod package:(Project currentPackageName)
+        newMethod package:(Project currentPackageName)
     ].
 
     install ifTrue:[
-	aClass addSelector:sel withMethod:newMethod
+        aClass addSelector:sel withMethod:newMethod
     ].
 
     silencio ifFalse:[
-	Transcript showCr:('    compiled: ', aClass name,' ', sel)
+        Transcript showCr:('    compiled: ', aClass name,' ', sel)
     ].
 
     ^ newMethod
 
     "Created: 29.10.1995 / 19:59:36 / cg"
+    "Modified: 13.12.1995 / 20:42:56 / cg"
 !
 
 compile:methodText forClass:classToCompileFor notifying:requestor
@@ -1585,7 +1621,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
@@ -1596,15 +1632,15 @@
      initName newMethod ok status className sep class stcPath 
      errorStream errorMessages eMsg m|
 
-    ObjectFileLoader isNil ifTrue:[^ #Error].
-    STCCompilation == #never ifTrue:[^ #Error].
+    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.
-	^ #Error
+        self parseError:'no stc compiler available - cannot create machine code' position:1.
+        ^ #CannotLoad
     ].
 
     SequenceNumber isNil ifTrue:[
-	SequenceNumber := 0.
+        SequenceNumber := 0.
     ].
     SequenceNumber := SequenceNumber + 1.
 
@@ -1615,16 +1651,16 @@
 
     class := aClass.
     class isMeta ifTrue:[
-	class := aClass soleInstance
+        class := aClass soleInstance
     ].
     class allSuperclasses reverseDo:[:cls|
-	cls ~~ Object ifTrue:[
-	    cls isLoaded ifFalse:[
-		^ #Error
-	    ].
-	    cls fileOutDefinitionOn:stream.
-	    stream nextPut:sep; cr.
-	]
+        cls ~~ Object ifTrue:[
+            cls isLoaded ifFalse:[
+                ^ #CannotLoad
+            ].
+            cls fileOutDefinitionOn:stream.
+            stream nextPut:sep; cr.
+        ]
     ].
     class fileOutDefinitionOn:stream.
     stream nextPut:sep; cr.
@@ -1635,9 +1671,9 @@
     className := aClass name.
 
     aClass isMeta ifTrue:[
-	stream nextPutAll:(className copyTo:(className size - 5)); nextPutAll:' class'.
+        stream nextPutAll:(className copyTo:(className size - 5)); nextPutAll:' class'.
     ] ifFalse:[
-	stream nextPutAll:className.
+        stream nextPutAll:className.
     ].
     stream nextPutAll:' methodsFor:'''; nextPutAll:cat; nextPutAll:''''.
     stream nextPut:sep.
@@ -1656,13 +1692,13 @@
 
     flags := '-commonSymbols +sharedLibCode +newIncremental -E:errorOutput -N' , initName .
     STCCompilationDefines notNil ifTrue:[
-	flags := STCCompilationDefines , ' ' , flags
+        flags := STCCompilationDefines , ' ' , flags
     ].
     STCCompilationIncludes notNil ifTrue:[
-	flags := STCCompilationIncludes , ' ' , flags
+        flags := STCCompilationIncludes , ' ' , flags
     ].
     STCCompilationOptions notNil ifTrue:[
-	flags := STCCompilationOptions , ' ' , flags
+        flags := STCCompilationOptions , ' ' , flags
     ].
 
     command := stcPath , ' ' , flags , ' -c ' , stFileName.
@@ -1673,72 +1709,80 @@
 
     "for debugging - leave c intermediate"
     STCKeepCIntermediate == true ifTrue:[
-	command := stcPath , ' ' , flags , ' -C ' , stFileName.
-	command printNL.
-	OperatingSystem executeCommand:command
+        command := stcPath , ' ' , flags , ' -C ' , stFileName.
+        command printNL.
+        OperatingSystem executeCommand:command
     ].
 
     oFileName asFilename exists ifTrue:[
-	ok ifFalse:[
-	    'oops - system says it failed - but o-file is there ...' printNL.
-	    ok := true
-	]
+        ok ifFalse:[
+            'oops - system says it failed - but o-file is there ...' printNL.
+            ok := true
+        ]
     ] ifFalse:[
-	ok := false
+        ok := false
     ].
 
     ok ifFalse:[
-	status >= 16r200 ifTrue:[
-	    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 asString
-		].
-	    ].
-	    errorMessages isNil ifTrue:[
-		errorMessages := ''
-	    ].
-	    eMsg := ('STC error during compilation:\',errorMessages) withCRs.
-	] ifFalse:[
-	    eMsg := 'oops, no STC - cannot create machine code'
-	].
-	self parseError:eMsg position:1.
-	OperatingSystem removeFile:stFileName.
-	^ #Error
+        status >= 16r200 ifTrue:[
+            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))
+"/                        ] ifFalse:[
+"/                            line
+"/                        ]
+"/                      ].
+                    errorMessages := errorMessages asString
+                ].
+            ].
+            errorMessages isNil ifTrue:[
+                errorMessages := ''
+            ].
+            eMsg := ('STC / CC error during compilation:\\',errorMessages) withCRs.
+        ] ifFalse:[
+            eMsg := 'oops, no STC - cannot create machine code'
+        ].
+        'errorOutput' asFilename remove.
+        self parseError:eMsg position:1.
+        OperatingSystem removeFile:stFileName.
+        ^ #Error
     ].
 
     (ObjectFileLoader notNil 
     and:[ObjectFileLoader canLoadObjectFiles]) ifFalse:[
-	self parseError:'no dynamic load configured - cannot load machine code' position:1.
-	OperatingSystem removeFile:stFileName.
-	^ #Error
+        self parseError:'no dynamic load configured - cannot load machine code' position:1.
+        OperatingSystem removeFile:stFileName.
+        ^ #CannotLoad
     ].
 
     OperatingSystem getOSType = 'irix' ifTrue:[
-	"
-	 link it to a shared object
-	"
-	soFileName := './' , initName , '.so'. 
-	OperatingSystem executeCommand:'rm -f ' , soFileName.
-	OperatingSystem executeCommand:'ld -shared -all -o ' , soFileName , ' ' , oFileName.
-	OperatingSystem removeFile:oFileName.
-	oFileName := soFileName. 
+        "
+         link it to a shared object
+        "
+        soFileName := './' , initName , '.so'. 
+        OperatingSystem executeCommand:'rm -f ' , soFileName.
+        OperatingSystem executeCommand:'ld -shared -all -o ' , soFileName , ' ' , oFileName.
+        OperatingSystem removeFile:oFileName.
+        oFileName := soFileName. 
     ] ifFalse:[
-	OperatingSystem getOSType = 'sys5_4' ifTrue:[
-	    "
-	     link it to a shared object
-	    "
-	    soFileName := './' , initName , '.so'. 
-	    OperatingSystem executeCommand:'rm -f ' , soFileName.
-	    OperatingSystem executeCommand:'ld -G -o ' , soFileName , ' ' , oFileName.
-	    OperatingSystem removeFile:oFileName.
-	    oFileName := soFileName. 
-	].
+        OperatingSystem getOSType = 'sys5_4' ifTrue:[
+            "
+             link it to a shared object
+            "
+            soFileName := './' , initName , '.so'. 
+            OperatingSystem executeCommand:'rm -f ' , soFileName.
+            OperatingSystem executeCommand:'ld -G -o ' , soFileName , ' ' , oFileName.
+            OperatingSystem removeFile:oFileName.
+            oFileName := soFileName. 
+        ].
     ].
 
     "
@@ -1746,125 +1790,125 @@
     "
     handle := ObjectFileLoader loadDynamicObject:oFileName.
     handle isNil ifTrue:[
-	OperatingSystem removeFile:stFileName.
-	OperatingSystem removeFile:oFileName.
-	self parseError:'dynamic load failed - cannot create machine code' position:1.
-	^ #Error
+        OperatingSystem removeFile:stFileName.
+        OperatingSystem removeFile:oFileName.
+        self parseError:'dynamic load failed - cannot create machine code' position:1.
+        ^ #CannotLoad
     ].
 "/    ('handle is ' , handle printString) printNL.
 
     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'
-	    ].
+        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.
+            ObjectFileLoader unloadDynamicObject:handle.
 
-	    OperatingSystem removeFile:stFileName.
-	    OperatingSystem removeFile:oFileName.
-	    self parseError:(eMsg , ' - cannot create machine code') position:1.
-	    ^ #Error
-	]
+            OperatingSystem removeFile:stFileName.
+            OperatingSystem removeFile:oFileName.
+            self parseError:(eMsg , ' - cannot create machine code') position:1.
+            ^ #CannotLoad
+        ]
     ].
 
 "/    ('init at ' , address printString) printNL.
 
     m := ObjectFileLoader 
-	callInitFunctionAt:address 
-	specialInit:true
-	forceOld:true 
-	interruptable:false
-	argument:2
-	identifyAs:handle
-	returnsObject:true.
+        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:[
-	    'BCOMPILER: oops - loaded method installed itself elsewhere' errorPrintNL.
-	].
+        m ~~ newMethod ifTrue:[
+            'BCOMPILER: oops - loaded method installed itself elsewhere' errorPrintNL.
+        ].
 
-	newMethod source:aString.
-	Project notNil ifTrue:[
-	    newMethod package:(Project currentPackageName)
-	].
+        newMethod source:aString.
+        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.
+        aClass addChangeRecordForMethod:newMethod.
+        (silent or:[Smalltalk silentLoading == true]) ifFalse:[
+            Transcript showCr:('    compiled: ', className,' ',selector,' - machine code')
+        ].
+        ObjectMemory flushCaches.
 
-	OperatingSystem removeFile:stFileName.
+        OperatingSystem removeFile:stFileName.
 
-	handle method:newMethod.
+        handle method:newMethod.
 
-	"/ check for obsolete loaded objects and unload them
+        "/ 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.
+        ObjectFileLoader loadedObjectHandlesDo:[:anotherHandle |
+            anotherHandle isMethodHandle ifTrue:[
+                anotherHandle method isNil ifTrue:[
+                    ObjectFileLoader unloadObjectFile:anotherHandle pathName.
+                    OperatingSystem removeFile:anotherHandle pathName.
+                ]
+            ]
+        ].
+        ^ newMethod.
     ].
 
     OperatingSystem removeFile:stFileName.
     OperatingSystem removeFile:oFileName.
     self parseError:'dynamic load failed' position:1.
-    ^ #Error
+    ^ #CannotLoad
 
     "
      |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: 6.12.1995 / 13:16:17 / cg"
+    "Modified: 13.12.1995 / 20:19:32 / cg"
 !
 
 trappingStubMethodFor:aString inCategory:cat
@@ -1894,5 +1938,5 @@
 !ByteCodeCompiler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/ByteCodeCompiler.st,v 1.55 1995-12-07 23:41:38 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/ByteCodeCompiler.st,v 1.56 1995-12-13 19:45:43 cg Exp $'
 ! !