ByteCodeCompiler.st
changeset 742 73b6a9c187f3
parent 736 0d0283353930
child 751 4f112db52253
--- a/ByteCodeCompiler.st	Wed Jul 15 18:16:18 1998 +0200
+++ b/ByteCodeCompiler.st	Wed Jul 15 18:16:56 1998 +0200
@@ -54,37 +54,37 @@
 
     [Instance variables:]
 
-        codeBytes       <ByteArry>              bytecodes
-        codeIndex       <SmallInteger>          next index to put into code array
-        litArray        <OrderedCollection>     literals
-        stackDelta      <SmallInteger>          return value of byteCodeFor:
-        extra           <Symbol>                return value of byteCodeFor:
-        lineno          <Boolean>               return value of byteCodeFor:
-        extraLiteral    <Symbol>                return value of byteCodeFor:
-        maxStackDepth   <SmallInteger>          stack need of method
-        relocList       <Array>                 used temporary for relocation
+	codeBytes       <ByteArry>              bytecodes
+	codeIndex       <SmallInteger>          next index to put into code array
+	litArray        <OrderedCollection>     literals
+	stackDelta      <SmallInteger>          return value of byteCodeFor:
+	extra           <Symbol>                return value of byteCodeFor:
+	lineno          <Boolean>               return value of byteCodeFor:
+	extraLiteral    <Symbol>                return value of byteCodeFor:
+	maxStackDepth   <SmallInteger>          stack need of method
+	relocList       <Array>                 used temporary for relocation
 
     [Class variables:]
 
-        JumpToAbsJump   <Dictionary>            internal table to map opcodes
-
-        SequenceNumber  <Integer>               counting intermediate stc-compiled
-                                                objects (for unique o-file naming)
-
-        STCCompilationDefines                   passed to stc as command line arguments
-        STCCompilationIncludes
-        STCCompilationOptions
-                        <String>                
-
-        STCCompilation  <Symbol>                #always, #primitiveOnly or #never
-                                                controls when stc compilation is wanted
-
-        ShareCode       <Boolean>               reuse byteArrays for common (simple) code sequences
-                                                This is normally a 'good' optimization,
-                                                expect if you plan to modify the byteCodes.
+	JumpToAbsJump   <Dictionary>            internal table to map opcodes
+
+	SequenceNumber  <Integer>               counting intermediate stc-compiled
+						objects (for unique o-file naming)
+
+	STCCompilationDefines                   passed to stc as command line arguments
+	STCCompilationIncludes
+	STCCompilationOptions
+			<String>                
+
+	STCCompilation  <Symbol>                #always, #primitiveOnly or #never
+						controls when stc compilation is wanted
+
+	ShareCode       <Boolean>               reuse byteArrays for common (simple) code sequences
+						This is normally a 'good' optimization,
+						expect if you plan to modify the byteCodes.
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
 "
 ! !
@@ -191,7 +191,7 @@
 !
 
 compile:aString forClass:aClass inCategory:cat notifying:requestor
-                 install:install skipIfSame:skipIfSame silent:silent foldConstants:fold
+		 install:install skipIfSame:skipIfSame silent:silent foldConstants:fold
 
     "the basic workhorse method for compiling:
      compile a source-string for a method in classToCompileFor.
@@ -211,8 +211,8 @@
 
     aString isNil ifTrue:[^ nil].
     silencio := silent 
-                or:[Smalltalk silentLoading == true
-                or:[ListCompiledMethods == false]].
+		or:[Smalltalk silentLoading == true
+		or:[ListCompiledMethods == false]].
 
     "lazy compilation is EXPERIMENTAL"
     lazy := (LazyCompilation == true) and:[install].
@@ -225,115 +225,115 @@
     compiler notifying:requestor.
     silent ifTrue:[
 "/        compiler ignoreErrors.
-        compiler ignoreWarnings.
-        compiler warnUndeclared:false.
+	compiler ignoreWarnings.
+	compiler warnUndeclared:false.
     ].
 "/    compiler nextToken.
 
     (compiler parseMethodSpec == #Error) ifTrue:[
-        compiler parseError:'syntax error in method specification'.
-        tree := #Error
+	compiler parseError:'syntax error in method specification'.
+	tree := #Error
     ] ifFalse:[
-        lazy ifTrue:[
-            "/
-            "/ that one method IS required
-            "/
-            (aClass isMeta and:[compiler selector == #version]) ifTrue:[
-                lazy := false
-            ]
-        ].
-
-        lazy 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.    
+	lazy ifTrue:[
+	    "/
+	    "/ that one method IS required
+	    "/
+	    (aClass isMeta and:[compiler selector == #version]) ifTrue:[
+		lazy := false
+	    ]
+	].
+
+	lazy 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.    
 "/                                aClass updateRevisionString.
-                                aClass addChangeRecordForMethodCategory:oldMethod category:cat.
-                                silencio ifFalse:[
-                                    Transcript showCR:('    (category change only)')
-                                ].
-                            ].
-                            "
-                             and package may be too.
-                            "
-                            pkg := Class packageQuerySignal raise.
-                            (pkg notNil and:[pkg ~~ oldMethod package]) ifTrue:[
-                                oldMethod package:pkg.
-                                silencio ifFalse:[
-                                    Transcript showCR:('    (package-id change only)')
-                                ].
-                            ].
-                            ^ oldMethod
-                        ]
-                    ]
-                ]
-            ].
-            tree := compiler parseMethodBody.
-            compiler tree:tree.
-        ]
+				aClass addChangeRecordForMethodCategory:oldMethod category:cat.
+				silencio ifFalse:[
+				    Transcript showCR:('    (category change only)')
+				].
+			    ].
+			    "
+			     and package may be too.
+			    "
+			    pkg := Class packageQuerySignal raise.
+			    (pkg notNil and:[pkg ~~ oldMethod package]) ifTrue:[
+				oldMethod package:pkg.
+				silencio ifFalse:[
+				    Transcript showCR:('    (package-id change only)')
+				].
+			    ].
+			    ^ oldMethod
+			]
+		    ]
+		]
+	    ].
+	    tree := compiler parseMethodBody.
+	    compiler tree:tree.
+	]
     ].
 
     (compiler errorFlag or:[tree == #Error]) ifTrue:[
-        compiler showErrorMessageForClass:aClass.
-        ^ #Error
+	compiler showErrorMessageForClass:aClass.
+	^ #Error
     ].
 
     sel := compiler selector.
     "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
     ].
 
     lazy ifFalse:[
-        "
-         freak-out support ...
-        "
-        ((compiler hasNonOptionalPrimitiveCode 
-        or:[(compiler hasPrimitiveCode and:[self canCreateMachineCode])
-        or:[STCCompilation == #always and:[sel ~~ #doIt]]])
-        and:[STCCompilation ~~ #never]) ifTrue:[
-            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:
+	"
+	 freak-out support ...
+	"
+	((compiler hasNonOptionalPrimitiveCode 
+	or:[(compiler hasPrimitiveCode and:[self canCreateMachineCode])
+	or:[STCCompilation == #always and:[sel ~~ #doIt]]])
+	and:[STCCompilation ~~ #never]) ifTrue:[
+	    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 for ''' , aClass name , '>>' , compiler selector , '''
 is not possible or disabled.
 
@@ -346,42 +346,42 @@
 
 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
-        ].
+				     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
+	].
     ].
 
     compiler hasNonOptionalPrimitiveCode ifTrue:[
-        newMethod := compiler trappingStubMethodFor:aString inCategory:cat.
-        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
+	newMethod := compiler trappingStubMethodFor:aString inCategory:cat.
+	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
     ].
 
     "
@@ -390,59 +390,59 @@
      compile itself when first called.
     "
     lazy ifTrue:[
-        newMethod := LazyMethod new.
-        (ClassCategoryReader sourceMode == #sourceReference) ifTrue:[
-            sourceFile := ObjectMemory nameForSources.
-            sourceFile notNil ifTrue:[    
-                sourceStream := sourceFile asFilename appendingWriteStream.
-            ]
-        ].
-        sourceStream isNil ifTrue:[
-            newMethod source:aString string.
-        ] ifFalse:[
-            sourceStream setToEnd.
-            pos := sourceStream position.
-            sourceStream nextChunkPut:aString.
-            sourceStream close.
-            newMethod sourceFilename:sourceFile position:pos.
-        ].
-        newMethod category:cat.
-        newMethod package:(Class packageQuerySignal raise).
+	newMethod := LazyMethod new.
+	(ClassCategoryReader sourceMode == #sourceReference) ifTrue:[
+	    sourceFile := ObjectMemory nameForSources.
+	    sourceFile notNil ifTrue:[    
+		sourceStream := sourceFile asFilename appendingWriteStream.
+	    ]
+	].
+	sourceStream isNil ifTrue:[
+	    newMethod source:aString string.
+	] ifFalse:[
+	    sourceStream setToEnd.
+	    pos := sourceStream position.
+	    sourceStream nextChunkPut:aString.
+	    sourceStream close.
+	    newMethod sourceFilename:sourceFile position:pos.
+	].
+	newMethod category:cat.
+	newMethod package:(Class packageQuerySignal raise).
 "/        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.
-
-        (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
-        ].
+	"
+	 produce symbolic code first
+	"
+	symbolicCodeArray := compiler genSymbolicCode.
+
+	(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
+	].
     ].
 
     "
@@ -450,9 +450,9 @@
     "
     newMethod := compiler createMethod.
     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).
@@ -462,9 +462,9 @@
      if there where any corrections, install the updated source
     "
     (newSource := compiler correctedSource) notNil ifTrue:[
-        newMethod source:newSource string
+	newMethod source:newSource string
     ] ifFalse:[
-        newMethod source:aString string.
+	newMethod source:aString string.
     ].
     newMethod category:cat.
     newMethod package:(Class packageQuerySignal raise).
@@ -473,11 +473,11 @@
 "/    ].
 
     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
@@ -589,6 +589,7 @@
 
     "
      Compiler ccCompilationOptions:'-O'
+     Compiler ccCompilationOptions:'-O -fPIC'
      Compiler ccCompilationOptions
     "
 
@@ -636,7 +637,7 @@
     |f|
 
     STC notNil ifTrue:[
-        ^ STC
+	^ STC
     ].
     (f := self stcPathOf:'stc') notNil ifTrue:[^ f].
     ^ self stcPathOf:'demostc'
@@ -729,12 +730,12 @@
 
     libDir := OperatingSystem getEnvironment:'STX_LIBDIR'.
     (libDir notNil and:[libDir asFilename exists]) ifTrue:[
-        incDir := libDir asFilename construct:'include'.
-        incDir exists ifTrue:[
-            (STCCompilationIncludes asCollectionOfWords includes:('-I' , incDir pathName)) ifFalse:[
-                STCCompilationIncludes := aString , ' ' , ('-I' , incDir pathName).
-            ]
-        ]
+	incDir := libDir asFilename construct:'include'.
+	incDir exists ifTrue:[
+	    (STCCompilationIncludes asCollectionOfWords includes:('-I' , incDir pathName)) ifFalse:[
+		STCCompilationIncludes := aString , ' ' , ('-I' , incDir pathName).
+	    ]
+	]
     ]
 
     "
@@ -931,25 +932,25 @@
     |index "{ Class: SmallInteger }" class|
 
     litArray isNil ifTrue:[
-        litArray := Array with:anObject.
-        ^ 1
+	litArray := Array with:anObject.
+	^ 1
     ].
     index := litArray identityIndexOf:anObject.
     (index == 0) ifTrue:[
-        "
-         reuse constants if same value and same class
-        "
-        class := anObject class.
-        ((class == Float) 
-        or:[class == Fraction
-        or:[class == LargeInteger
-        "or:[class == String] --only if literalString option has been added---" ]]) ifTrue:[
-            index := litArray indexOf:anObject.
-        ].
-        ((index == 0) or:[(litArray at:index) class ~~ class]) ifTrue:[
-            litArray := litArray copyWith:anObject.
-            ^ litArray size
-        ].
+	"
+	 reuse constants if same value and same class
+	"
+	class := anObject class.
+	((class == Float) 
+	or:[class == Fraction
+	or:[class == LargeInteger
+	"or:[class == String] --only if literalString option has been added---" ]]) ifTrue:[
+	    index := litArray indexOf:anObject.
+	].
+	((index == 0) or:[(litArray at:index) class ~~ class]) ifTrue:[
+	    litArray := litArray copyWith:anObject.
+	    ^ litArray size
+	].
     ].
     ^ index
 
@@ -1678,13 +1679,13 @@
 
     newMethod := Method new:(litArray size).
     litArray notNil ifTrue:[
-        "/ fixup CheapBlocks method-field in literal array,
-        litArray do:[:aLiteral |
-            (aLiteral isMemberOf:CheapBlock) ifTrue:[
-                aLiteral setMethod:newMethod.
-            ]
-        ].
-        newMethod literals:litArray
+	"/ fixup CheapBlocks method-field in literal array,
+	litArray do:[:aLiteral |
+	    (aLiteral isMemberOf:CheapBlock) ifTrue:[
+		aLiteral setMethod:newMethod.
+	    ]
+	].
+	newMethod literals:litArray
     ].
 
     newMethod numberOfVars:(self numberOfMethodVars + (maxNumTemp ? 0)).
@@ -1692,7 +1693,7 @@
     newMethod stackSize:(self maxStackDepth).
 
     primitiveResource notNil ifTrue:[
-        newMethod setResourceFlag
+	newMethod setResourceFlag
     ].
 
     ^ newMethod
@@ -2016,12 +2017,12 @@
     (sel == #bitOr:)  ifTrue:[^ true].
     (sel == #new:)    ifTrue:[^ true].
     (sel == #basicNew:) ifTrue:[
-        "/ this one is critical - some redefine it
-        receiver isGlobal ifTrue:[
-            (#('String' 'ByteArray' 'Array'
-              'Point' 'Rectangle' 'Object')
-            includes:receiver name) ifTrue:[^ true].
-        ].
+	"/ this one is critical - some redefine it
+	receiver isGlobal ifTrue:[
+	    (#('String' 'ByteArray' 'Array'
+	      'Point' 'Rectangle' 'Object')
+	    includes:receiver name) ifTrue:[^ true].
+	].
     ].
     ^ false
 
@@ -2075,12 +2076,12 @@
 
     (sel == #new)    ifTrue:[^ true].
     (sel == #basicNew) ifTrue:[
-        "/ this one is critical - some redefine it
-        receiver isGlobal ifTrue:[
-            (#('String' 'ByteArray' 'Array'
-               'Point' 'Rectangle' 'Object')
-            includes:receiver name) ifTrue:[^ true].
-        ].
+	"/ this one is critical - some redefine it
+	receiver isGlobal ifTrue:[
+	    (#('String' 'ByteArray' 'Array'
+	       'Point' 'Rectangle' 'Object')
+	    includes:receiver name) ifTrue:[^ true].
+	].
     ].
     ^ false
 
@@ -2315,24 +2316,24 @@
      adding any here requires a new VM (i.e. you cannot change it)"
 
     ^ #(
-        #Array                  "/ 0
-        #String                 "/ 1
-        #FloatArray             "/ 2
-        #DoubleArray            "/ 3
-        #Point                  "/ 4
-        #Symbol                 "/ 5
-        #Smalltalk              "/ 6
-        #Processor              "/ 7
-        #SmallInteger           "/ 8
-        #Character              "/ 9
-        #Float                  "/ 10
-        #Process                "/ 11
-        #Set                    "/ 12
-        #IdentitySet            "/ 13
-        #Dictionary             "/ 14
-        #IdentityDictionary     "/ 15
-        #Sempahore              "/ 16
-        #OrderedCollection      "/ 17
+	#Array                  "/ 0
+	#String                 "/ 1
+	#FloatArray             "/ 2
+	#DoubleArray            "/ 3
+	#Point                  "/ 4
+	#Symbol                 "/ 5
+	#Smalltalk              "/ 6
+	#Processor              "/ 7
+	#SmallInteger           "/ 8
+	#Character              "/ 9
+	#Float                  "/ 10
+	#Process                "/ 11
+	#Set                    "/ 12
+	#IdentitySet            "/ 13
+	#Dictionary             "/ 14
+	#IdentityDictionary     "/ 15
+	#Sempahore              "/ 16
+	#OrderedCollection      "/ 17
        )
 
     "Created: 4.6.1997 / 12:17:47 / cg"
@@ -2357,20 +2358,20 @@
      adding any here requires a new VM (i.e. you cannot change it)"
 
     ^ #(
-        #top                    "/ 0
-        #bottom                 "/ 1
-        #left                   "/ 2
-        #right                  "/ 3
-        #x                      "/ 4
-        #y                      "/ 5
-        #width                  "/ 6
-        #height                 "/ 7
-        #origin                 "/ 8
-        #extent                 "/ 9
-        #asInteger              "/ 10
-        #rounded                "/ 11
-        #next                   "/ 12
-        #peek                   "/ 13
+	#top                    "/ 0
+	#bottom                 "/ 1
+	#left                   "/ 2
+	#right                  "/ 3
+	#x                      "/ 4
+	#y                      "/ 5
+	#width                  "/ 6
+	#height                 "/ 7
+	#origin                 "/ 8
+	#extent                 "/ 9
+	#asInteger              "/ 10
+	#rounded                "/ 11
+	#next                   "/ 12
+	#peek                   "/ 13
        )
 
     "Created: 4.6.1997 / 12:20:28 / cg"
@@ -2403,7 +2404,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
@@ -2421,19 +2422,25 @@
     (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
+    ].
+
+    (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
@@ -2441,7 +2448,7 @@
     "/ lifes
 
     SequenceNumber isNil ifTrue:[
-        SequenceNumber := 0.
+	SequenceNumber := 0.
     ].
     SequenceNumber := SequenceNumber + 1.
 
@@ -2450,182 +2457,182 @@
     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
     ].
 
     [
-        |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|
-                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:[
-                        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 := './' , 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 := ''
-        ].
-        (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.
+	|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|
+		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:[
+			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 := './' , initName , (ObjectFileLoader objectFileExtension). 
+	cFileName := './' , initName , '.c'. 
+	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.
 
 "/        '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.
-                    errorStream close.
-                    errorMessages notNil ifTrue:[
-                        errorMessages := errorMessages asStringCollection.
-                        errorMessages size > 20 ifTrue:[
-                            errorMessages := (errorMessages copyTo:20) copyWith:'... more messages skipped'
-                        ].
+	    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'
+			].
     "/                    errorMessages := errorMessages collect:[:line |
     "/                        (line startsWith:(stFileName , ':')) ifTrue:[
     "/                            'Line: ' , (line copyFrom:(stFileName size + 2))
@@ -2633,215 +2640,213 @@
     "/                            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'.
-
-        (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
+	    ].
+	    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 , '/' , initName , '.' , (oFileName asFilename suffix).
+	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
+	].
     "/    ('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.
+	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 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.
-        ].
+	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
     "
 
@@ -2858,7 +2863,7 @@
 
     newMethod := Method new:(litArray size).
     litArray notNil ifTrue:[
-        newMethod literals:litArray
+	newMethod literals:litArray
     ].
 
     newMethod makeUncompiled.
@@ -2891,6 +2896,6 @@
 !ByteCodeCompiler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/ByteCodeCompiler.st,v 1.137 1998-06-18 15:39:58 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/ByteCodeCompiler.st,v 1.138 1998-07-15 16:16:56 cg Exp $'
 ! !
 ByteCodeCompiler initialize!