checkin from browser
authorClaus Gittinger <cg@exept.de>
Mon, 08 Oct 2001 11:46:53 +0200
changeset 6082 55dba32ef74e
parent 6081 fedbf974cfe8
child 6083 98a14d57e673
checkin from browser
Metaclass.st
--- a/Metaclass.st	Mon Oct 08 11:44:52 2001 +0200
+++ b/Metaclass.st	Mon Oct 08 11:46:53 2001 +0200
@@ -150,400 +150,6 @@
     builder := ClassBuilder new.
     builder oldMetaclass:self instanceVariableNames:aString.
     builder rebuildForChangedInstanceVariables.
-!
-
-xx_instanceVariableNames:aString
-    "changing / adding class-inst vars -
-     this actually creates a new metaclass and class, leaving the original
-     classes around as obsolete classes. This may also be true for all subclasses,
-     if class instance variables are added/removed.
-     Existing instances continue to be defined by their original classes.
-
-     Time will show, if this is an acceptable behavior or if we should migrate
-     instances to become insts. of the new classes."
-
-    |newClass newMetaclass nClassInstVars oldClass 
-     allSubclasses oldVars
-     oldNames newNames addedNames
-     oldOffsets newOffsets offset changeSet delta
-     oldToNew newSubMeta newSub oldSubMeta oldSuper
-     commonClassInstVars t|
-
-    "
-     cleanup needed here: extract common things with name:inEnvironment:...
-     and restructure things ... currently way too complex.
-    "
-
-    oldVars := self instanceVariableString.
-    aString = oldVars ifTrue:[
-"
-        Transcript showCR:'no change (', oldVars , ') -> (', aString , ')'.
-"
-        ^ self
-    ].
-
-    oldNames := oldVars asCollectionOfWords.
-    newNames := aString asCollectionOfWords.
-
-    oldNames = newNames ifTrue:[
-"
-        Transcript showCR:'no real change'.
-"
-        "no real change (just formatting)"
-        self setInstanceVariableString:aString.
-        ^ self
-    ]. 
-
-"/    "
-"/     let user confirm, if any name is no good (and was good before)
-"/    "
-"/    (oldNames inject:true
-"/                into:[:okSoFar :word |
-"/                         okSoFar and:[word first isUppercase]
-"/                     ])
-"/    ifTrue:[
-"/        "was ok before"
-"/        (newNames inject:true
-"/                    into:[:okSoFar :word |
-"/                             okSoFar and:[word first isUppercase]
-"/                         ])
-"/        ifFalse:[
-"/            (self confirm:'class instance variable names should start with an uppercase letter
-"/(by convention only)
-"/
-"/install anyway ?' withCRs)
-"/            ifFalse:[
-"/                ^ nil
-"/            ]
-"/        ]
-"/    ].
-
-    nClassInstVars := newNames size.
-
-"
-    Transcript showCR:'create new class/metaclass'.
-"
-
-    "
-     create the new metaclass
-    "
-    self isPrivate ifTrue:[
-        newMetaclass := PrivateMetaclass new.
-        newMetaclass setOwningClass:(self owningClass).
-    ] ifFalse:[
-        newMetaclass := Metaclass new.
-    ].
-    newMetaclass setSuperclass:superclass.
-    newMetaclass instSize:(superclass instSize + nClassInstVars).
-    (nClassInstVars ~~ 0) ifTrue:[
-        newMetaclass setInstanceVariableString:aString
-    ].
-"/    newMetaclass flags:(Behavior flagBehavior "flagNotIndexed").
-"/    newMetaclass setName:name.
-"/    newMetaclass classVariableString:classvars.
-"/    newMetaclass setComment:(self comment).
-
-    "find the class which is my sole instance"
-
-    oldClass := myClass.
-
-    "
-     create the new class
-    "
-    newClass := newMetaclass new.
-    newClass setSuperclass:(oldClass superclass).
-    newClass instSize:(oldClass instSize).
-    newClass flags:(oldClass flags).
-    newClass setName:(oldClass name).
-    newClass setInstanceVariableString:(oldClass instanceVariableString).
-    newClass classVariableString:(oldClass classVariableString).
-    newClass setComment:(oldClass comment).
-    newClass category:(oldClass category).
-    (t := oldClass primitiveSpec) notNil ifTrue:[
-        newClass primitiveSpec:t.
-    ].        
-    newClass setClassFilename:(oldClass classFilename).
-
-    "/ set the new classes package
-    "/ from the old package
-
-    newClass package:(oldClass package).
-
-    "/ and keep the binary revision
-    newClass setBinaryRevision:(oldClass binaryRevision).
-
-    changeSet := Set new.
-    ((oldNames size == 0) 
-    or:[newNames startsWith:oldNames]) ifTrue:[
-        "new variable(s) has/have been added - old methods still work"
-
-"/        Transcript showCR:'copying methods ...'.
-"/        Transcript endEntry.
-
-        self copyMethodsFrom:self for:newMetaclass.
-        self copyMethodsFrom:oldClass for:newClass.
-
-        "
-         but have to recompile methods accessing stuff now defined
-         (it might have been a global/undeclared before ...)
-        "
-
-        addedNames := newNames select:[:nm | (oldNames includes:nm) not].
-
-"/        Smalltalk silentLoading ifFalse:[
-"/            Transcript showCR:'recompiling class methods of ' , newMetaclass name ,
-"/                              ' accessing any of ' , addedNames printString.
-"/        ].
-
-        "recompile class-methods"    
-        newMetaclass recompileMethodsAccessingAny:addedNames.
-    ] ifFalse:[
-        "
-         create the changeSet; thats the set of class instvar names
-         which have changed their position or are new
-        "
-        offset := 0. oldOffsets := Dictionary new.
-        oldNames do:[:nm | offset := offset + 1. oldOffsets at:nm put:offset].
-        offset := 0. newOffsets := Dictionary new.
-        newNames do:[:nm | offset := offset + 1. newOffsets at:nm put:offset].
-
-        oldOffsets associationsDo:[:a |
-            |k|
-
-            k := a key.
-            (newOffsets includesKey:k) ifFalse:[
-                changeSet add:k
-            ] ifTrue:[
-                (a value ~~ (newOffsets at:k)) ifTrue:[
-                    changeSet add:k
-                ]
-            ]
-        ].
-        newOffsets associationsDo:[:a |
-            |k|
-
-            k := a key.
-            (oldOffsets includesKey:k) ifFalse:[
-                changeSet add:k
-            ] ifTrue:[
-                (a value ~~ (oldOffsets at:k)) ifTrue:[
-                    changeSet add:k
-                ]
-            ]
-        ].
-
-"/        Smalltalk silentLoading ifFalse:[
-"/            Transcript showCR:'recompiling class methods of ' , newMetaclass name ,
-"/                              ' accessing any of ' , changeSet printString.
-"/        ].
-
-        "
-         recompile class-methods accessing any c-instvar with a changed position
-        "
-        self copyInvalidatedMethodsFrom:self for:newMetaclass accessingAny:changeSet.
-        newMetaclass recompileInvalidatedMethods.
-
-        self copyMethodsFrom:oldClass for:newClass.
-    ].
-
-    delta := newNames size - oldNames size.
-
-    "/ preserve existing classInstVar values (but not those from Class)
-    newMetaclass allInstVarNames do:[:nm |
-        |v|
-
-        (Class class allInstVarNames includes:nm) ifFalse:[
-            v := oldClass instVarNamed:nm ifAbsent:nil.
-            v notNil ifTrue:[
-                newClass instVarNamed:nm put:v.    
-            ].
-        ].
-    ].
-
-    "
-     get list of all subclasses - do before superclass is changed
-    "
-    allSubclasses := oldClass allSubclasses asOrderedCollection.
-    "/ cg: wrong: allSubclasses := allSubclasses asSortedCollection:[:a :b | b isSubclassOf:a].
-    allSubclasses := allSubclasses topologicalSort:[:a :b | b isSubclassOf:a]. 
-
-    oldToNew := IdentityDictionary new.
-
-    "
-     create a new class tree, based on the new version
-    "
-    allSubclasses do:[:aSubclass |
-        oldSuper := aSubclass superclass.
-        oldSubMeta := aSubclass class.
-
-        newSubMeta := Metaclass new.
-        oldSuper == oldClass ifTrue:[
-            newSubMeta setSuperclass:newMetaclass.
-        ] ifFalse:[
-            newSubMeta setSuperclass:(oldToNew at:oldSuper) class.
-        ].
-        newSubMeta instSize:(oldSubMeta instSize + delta).
-        newSubMeta flags:(oldSubMeta flags).
-"/        newSubMeta setName:(oldSubMeta name).
-        newSubMeta setInstanceVariableString:(oldSubMeta instanceVariableString).
-"/        newSubMeta setComment:(oldSubMeta comment).
-
-        newSub := newSubMeta new.
-        oldSuper == oldClass ifTrue:[
-            newSub setSuperclass:newClass.
-        ] ifFalse:[
-            newSub setSuperclass:(oldToNew at:oldSuper).
-        ].
-
-"/        newSub setMethodDictionary:(aSubclass methodDictionary copy).
-"/        newSub class setMethodDictionary:(aSubclass class methodDictionary copy).
-        newSub setName:(aSubclass name).
-        newSub classVariableString:(aSubclass classVariableString).
-        newSub setInstanceVariableString:(aSubclass instanceVariableString).
-        (t := aSubclass primitiveSpec) notNil ifTrue:[
-            newSub primitiveSpec:t.
-        ].
-        newSub package:(aSubclass package).
-        newSub setClassFilename:(oldClass classFilename).
-        newSub setComment:(aSubclass comment).
-        newSub category:(aSubclass category).
-        newSub instSize:(aSubclass instSize).
-        newSub setBinaryRevision:(aSubclass binaryRevision).
-
-        oldToNew at:aSubclass put:newSub.
-
-        aSubclass category:#'* obsolete *'.
-
-        "/ preserve existing classInstVar values (but not those from Class)
-
-        newSubMeta allInstVarNames do:[:nm |
-            |v|
-
-            (Class class allInstVarNames includes:nm) ifFalse:[
-                v := aSubclass instVarNamed:nm ifAbsent:nil.
-                v notNil ifTrue:[
-                    newSub instVarNamed:nm put:v.    
-                ].
-            ].
-        ].
-
-    ].
-
-    "recompile what needs to be"
-
-    delta == 0 ifTrue:[
-        "only have to recompile class methods accessing 
-         class instvars from changeset
-        "
-
-        allSubclasses do:[:oldSubclass |
-            |newSubclass|
-
-            newSubclass := oldToNew at:oldSubclass.
-
-"/            Smalltalk silentLoading ifFalse:[
-"/                Transcript showCR:'recompiling class methods of ' , newSubclass class name ,
-"/                                  ' accessing any of ' , changeSet printString.
-"/            ].
-
-            self 
-                copyInvalidatedMethodsFrom:oldSubclass class for:newSubclass class 
-                accessingAny:changeSet orSuper:true.
-
-            self 
-                copyInvalidatedMethodsFrom:oldSubclass for:newSubclass 
-                accessingAny:#() orSuper:true.
-
-            newSubclass class recompileInvalidatedMethods.
-            newSubclass recompileInvalidatedMethods.
-        ]
-    ] ifFalse:[
-        "
-         have to recompile all class methods accessing class instvars
-        "
-        commonClassInstVars := oldClass class allInstVarNames.
-        changeSet do:[:v |
-            commonClassInstVars remove:v ifAbsent:[]
-        ].
-
-        allSubclasses do:[:oldSubclass |
-            |newSubclass classInstVars|
-
-            newSubclass := oldToNew at:oldSubclass.
-
-            classInstVars := newSubclass class allInstVarNames asSet.
-            classInstVars removeAll:commonClassInstVars.
-            classInstVars addAll:changeSet.
-
-"/            Smalltalk silentLoading ifFalse:[
-"/                Transcript showCR:'recompiling class methods of ' , newSubclass class name ,
-"/                                  ' accessing any of ' , classInstVars printString.
-"/            ].
-
-            self 
-                copyInvalidatedMethodsFrom:oldSubclass class for:newSubclass class 
-                accessingAny:classInstVars orSuper:true.
-
-            self 
-                copyInvalidatedMethodsFrom:oldSubclass for:newSubclass 
-                accessingAny:#() orSuper:true.
-
-            newSubclass class recompileInvalidatedMethods.
-            newSubclass recompileInvalidatedMethods.
-        ]
-    ].
-
-    newClass addChangeRecordForClassInstvars:newClass.
-
-    "install all new classes"
-
-    (Smalltalk at:(oldClass name asSymbol) ifAbsent:nil) == oldClass ifTrue:[
-        Smalltalk at:(oldClass name asSymbol) put:newClass.
-        self checkForAliasesOf:oldClass with:newClass.
-
-        "
-         change any private subclasses' owners
-        "
-        oldClass privateClassesDo:[:aClass |
-            aClass class setOwningClass:newClass
-        ].
-
-    ].
-    ObjectMemory flushCachesFor:oldClass.
-
-    allSubclasses do:[:oldSubClass |
-        |newSubClass|
-
-        newSubClass := oldToNew at:oldSubClass.
-
-"/        Transcript showCR:'install ' , newSubClass name , '(' , newSubClass category , ')' ,
-"/                          ' as ' , newSubClass name.
-
-        (Smalltalk at:(oldSubClass name asSymbol) ifAbsent:nil) == oldSubClass ifTrue:[
-            Smalltalk at:oldSubClass name asSymbol put:newSubClass.
-            self checkForAliasesOf:oldSubClass with:newSubClass.
-        ].
-        ObjectMemory flushCachesFor:oldSubClass.
-
-        oldSubClass privateClassesDo:[:aClass |
-            aClass class setOwningClass:newSubClass
-        ].
-    ].
-
-    "tell dependents ..."
-
-    oldClass changed:#definition.
-    self changed:#definition.
-    self nameSpace changed:#classDefinition with:self.
-    self nameSpace ~~ Smalltalk ifTrue:[
-        Smalltalk changed:#classDefinition with:self.
-    ].
-
-    ^ newMetaclass
-
-    "Created: / 29.10.1995 / 19:57:08 / cg"
-    "Modified: / 1.4.1997 / 15:44:09 / stefan"
-    "Modified: / 31.7.1998 / 18:02:00 / cg"
 ! !
 
 !Metaclass methodsFor:'compiler interface'!
@@ -736,393 +342,6 @@
     myClass := aClass
 
     "Created: 12.12.1995 / 13:46:22 / cg"
-!
-
-xx_checkConventionsFor:className subClassOf:aClass instVarNames:instVarNameString classVarNames:classVarNameString
-    "Check for some 'considered bad-style' things, like lower case names.
-     NOTICE:
-     I dont like the confirmers below - we need a notifying: argument, to give
-     the outer codeview a chance to highlight the error.
-     (but thats how its defined in the book - maybe I will change it anyway).
-    "
-
-    |names idx what doChecks answ|
-
-    doChecks := ConfirmationQuerySignal query.
-    doChecks == false ifTrue:[^ true].
-
-    "let user confirm, if the classname is no good"
-    className first isUppercase ifFalse:[
-        aClass == NameSpace ifTrue:[
-            what := 'namespace'
-        ] ifFalse:[
-            what := 'class'
-        ].
-
-        answ := Class classConventionViolationConfirmationQuerySignal query.
-        answ notNil ifTrue:[^ answ].
-
-        (self confirm:(what , ' name ''' , className , 
-                             ''' should start with an uppercase letter
-(by convention only)
-
-install anyway ?') withCRs)
-        ifFalse:[
-            ^ false
-        ]
-    ].
-
-    names := instVarNameString asCollectionOfWords.
-
-    "let user confirm, if any instvarname is no good"
-    (idx := names findFirst:[:word | word first isUppercase]) ~~ 0 ifTrue:[
-        answ := Class classConventionViolationConfirmationQuerySignal query.
-        answ notNil ifTrue:[^ answ].
-
-        (self confirm:className , ': instance variable named ''' , (names at:idx) allBold , ''' 
-should start with a lowercase letter (by convention only).
-
-Install anyway ?' withCRs)
-        ifFalse:[
-            ^ false
-        ]
-    ].
-
-    names := classVarNameString asCollectionOfWords. 
-
-    "let user confirm, if any classvarname is no good"
-    (idx := names findFirst:[:word | word first isLowercase]) ~~ 0 ifTrue:[
-        answ := Class classConventionViolationConfirmationQuerySignal query.
-        answ notNil ifTrue:[^ answ].
-
-        (self confirm:className , ': class variable named ''' , (names at:idx) allBold  , ''' 
-should start with an uppercase letter (by convention only).
-
-Install anyway ?' withCRs)
-        ifFalse:[
-            ^ false
-        ].
-    ].
-
-    ^ true
-
-    "Created: / 15.10.1996 / 11:56:38 / cg"
-    "Modified: / 3.2.1999 / 11:24:52 / cg"
-    "Modified: / 18.3.1999 / 18:22:47 / stefan"
-!
-
-xx_checkForAliasesOf:oldClass with:newClass
-    "oldClass changed its identity (now use newClass).
-     check if there are any global aliases, which should also be changed"
-
-    Smalltalk keysAndValuesDo:[:nm :o |
-        o == oldClass ifTrue:[
-            nm ~~ oldClass name ifTrue:[
-                (self confirm:('The global/classVar `' , nm , ''' is an alias for ' , oldClass name , '.\\Change it to the new class ?') withCRs)
-                ifTrue:[
-                    Smalltalk at:nm put:newClass
-                ]
-            ]
-        ]
-    ].
-
-    "Created: 22.10.1996 / 15:20:59 / cg"
-    "Modified: 22.10.1996 / 15:25:50 / cg"
-!
-
-xx_checkInstvarRedefsWith:stringOfInstVarNames subclassOf:aClass old:oldClass name:newName
-    |superInstVars msg|
-
-    aClass notNil ifTrue:[
-        "
-         check for instVar redef of superClass instVars
-        "
-        superInstVars := aClass allInstVarNames.
-        stringOfInstVarNames asCollectionOfWords do:[:nm |
-            (superInstVars includes:nm) ifTrue:[
-                (oldClass notNil 
-                and:[stringOfInstVarNames = oldClass instanceVariableString])
-                ifTrue:[
-                    Transcript showCR:('instVar conflict in `' , newName , ''' for `' , nm , ''' due to superclass change.').
-                    msg := 'instVar conflict in `' , newName , ''' for `' , nm , ''' due to superclass change.\You now have two different instVar slots with the same name.\\Dont forget to fix this later.'.
-                    self warn:msg withCRs.
-                ] ifFalse:[
-                    Transcript showCR:('instVar `' , nm , ''' is already defined in a superclass of `' , newName , '''.').
-                    msg := 'instVar `' , nm , ''' is already defined in a superclass.\Change the definition of `' , newName , ''' anyway ?\\Notice: you must fix the superclass later.'.
-                    ^ self confirm:msg withCRs
-                ].
-            ]
-        ].
-    ].
-
-    oldClass notNil ifTrue:[
-        "
-         check for instVar redefs in subclass instVars
-        "
-        oldClass allSubclassesDo:[:sub |
-            |vars|
-
-            vars := sub instVarNames.
-            stringOfInstVarNames asCollectionOfWords do:[:nm |
-                (vars includes:nm) ifTrue:[
-                    ^ self confirm:('subclass ' 
-                                    , sub name 
-                                    , ' already defines an instVar named `' 
-                                    , nm 
-                                    , '''.\\Change the definition of `' 
-                                    , newName 
-                                    , ''' anyway ?\Notice: you must fix the subclass later.'
-                                   ) withCRs
-                ]
-            ]
-        ]
-    ].
-    ^ true
-
-    "Created: 29.1.1997 / 17:42:11 / cg"
-!
-
-xx_checkValidVarNamesFor:className subClassOf:aClass instVarNames:instVarNameString classVarNames:classVarNameString
-    "Check for some 'considered bad-style' things, like lower case names.
-     NOTICE:
-     I dont like the confirmers below - we need a notifying: argument, to give
-     the outer codeview a chance to highlight the error.
-     (but thats how its defined in the book - maybe I will change it anyway).
-    "
-
-    |names|
-
-    names := instVarNameString asCollectionOfWords.
-
-    "check for instvar redefs within local instvars"
-    names keysAndValuesDo:[:index :aName |
-        (names indexOf:aName startingAt:index+1) ~~ 0 ifTrue:[
-            self warn:'instance variable ''' , aName , '''\occurs multiple times in instVarString.\\Class not installed.' withCRs.
-            ^ false.
-        ]
-    ].
-
-    names := classVarNameString asCollectionOfWords. 
-
-    "check for classvar redefs within local instvars"
-    names keysAndValuesDo:[:index :aName |
-        (names indexOf:aName startingAt:index+1) ~~ 0 ifTrue:[
-            self warn:'class variable ''' , aName , '''\occurs multiple times in classVarString.\\Class not installed.' withCRs.
-            ^ false.
-        ]
-    ].
-    ^ true
-
-    "Created: 8.1.1997 / 21:09:14 / cg"
-    "Modified: 9.1.1997 / 02:10:02 / cg"
-!
-
-xx_copyInvalidatedMethodsFrom:oldClass for:newClass
-    "copy all methods from oldClass to newClass and change their code
-     to a trap method reporting an error.
-     This is done when a class has changed its layout or inheritance,
-     before recompilation is attempted.
-     This allows us to keep the source while trapping uncompilable (due to
-     now undefined instvars) methods. Later compilation of these methods will show
-     an error on the transcript and lead to the debugger once called."
-
-    |trap trapCode trapByteCode oldMethod newMethod
-     oldDict newDict|
-
-    oldDict := oldClass methodDictionary.
-    newDict := MethodDictionary new:oldDict size.
-
-    oldDict keysAndValuesDo:[ :sel :mthd |
-        trap := mthd trapMethodForNumArgs:(mthd numArgs).
-        trapCode := trap code.
-        trapByteCode := trap byteCode.
-
-        mthd isWrapped ifTrue:[
-            oldMethod := mthd originalMethod
-        ] ifFalse:[
-            oldMethod := mthd.
-        ].
-
-        newMethod := oldMethod copy.
-        newMethod makeInvalid.
-        newDict at:sel put:newMethod
-    ].
-        
-    newClass methodDictionary:newDict.
-
-    "Modified: 12.6.1996 / 10:44:27 / stefan"
-    "Modified: 4.11.1996 / 22:55:57 / cg"
-!
-
-xx_copyInvalidatedMethodsFrom:oldClass for:newClass accessingAny:setOfNames
-    "copy all methods from oldClass to newClass. Those methods accessing
-     a variable in setOfNames will be copied as invalid method, leading to
-     a trap when its executed. This is used when a class has changed its
-     layout for all methods which are affected by the change."
-
-    self copyInvalidatedMethodsFrom:oldClass 
-                                for:newClass 
-                       accessingAny:setOfNames 
-                            orSuper:false 
-!
-
-xx_copyInvalidatedMethodsFrom:oldClass for:newClass accessingAny:setOfNames orSuper:superBoolean
-    "copy all methods from oldClass to newClass. 
-     Those methods accessing a variable in setOfNames will be copied as invalid method, 
-     leading to a trap when its executed. If superBoolean is true, this is also done
-     for methods accessing super.  This is used when a class has changed its
-     layout for all methods which are affected by the change."
-
-    |p source mustInvalidate
-     oldMethod newMethod methodDict newMethodDict nNames|
-
-    methodDict := oldClass methodDictionary.
-    newMethodDict := methodDict copy.
-    nNames := setOfNames size.
-
-    methodDict keysAndValuesDo:[:selector :method |
-        method isWrapped ifTrue:[
-            oldMethod := method originalMethod
-        ] ifFalse:[
-            oldMethod := method
-        ].
-
-        "before parsing (which may take some time),
-         do a string search if its only one variable,
-         we are looking for.
-         Could look for more than one variable by string compare, but then
-         parsing it right away may be faster ..."
-
-        source := oldMethod source.
-        ((nNames == 1) and:[superBoolean not]) ifTrue:[
-            mustInvalidate := (source findString:(setOfNames first)) ~~ 0.
-        ] ifFalse:[
-            ((nNames == 0) and:[superBoolean]) ifTrue:[
-                mustInvalidate := (source findString:'super') ~~ 0.
-            ] ifFalse:[
-                mustInvalidate := true
-            ].
-        ].
-
-        mustInvalidate ifTrue:[
-            "we have to parse it ..."
-            p := Parser parseMethod:source in:newClass.
-            (p isNil 
-             or:[(p usedVars includesAny:setOfNames)
-             or:[superBoolean and:[p usesSuper]]]) ifFalse:[
-                mustInvalidate := false
-            ]
-        ].
-
-        mustInvalidate ifTrue:[
-            newMethod := oldMethod copy.
-"/            Smalltalk silentLoading ifFalse:[
-"/                Transcript showCR:'invalidating ' , selector , '...'.
-"/            ].
-            newMethod makeInvalid.
-        ] ifFalse:[
-            newMethod := oldMethod.
-            newMethod mclass:nil.
-        ].
-        newMethodDict at:selector put:newMethod
-    ].
-    newClass methodDictionary:newMethodDict.
-
-    "Modified: 7.6.1996 / 08:33:52 / stefan"
-    "Modified: 19.6.1997 / 18:27:09 / cg"
-!
-
-xx_copyMethodsFrom:oldClass for:newClass
-    "copy all methods from oldClass to newClass.
-     This is used for class-methods when a class has changed, but its metaclass is 
-     unaffected (i.e. classVars/inheritance have not changed) so there is no need
-     to recompile the class methods."
-
-    newClass methodDictionary:(oldClass methodDictionary copy).
-    newClass methodDictionary keysAndValuesDo:[:sel :mthd | mthd mclass:nil.].
-
-    "Modified: 7.6.1996 / 08:34:43 / stefan"
-!
-
-xx_differentInstanceVariableOffsetsIn:class1 and:class2
-    "return a set of instance variable names which have different
-     positions in class1 and class2.
-     Also, variables which are only present in one class are returned.
-     This is used to find methods which need recompilation after a
-     change in the instance variable layout."
-
-    |offsets1 offsets2 changeSet|
-
-    changeSet := Set new.
-
-    "
-     collect the instvar-indices in the old and new class
-    "
-    offsets1 := class1 instanceVariableOffsets.
-    offsets2 := class2 instanceVariableOffsets.
-
-    "
-     compute the changeset as a set of instance variables, 
-     which have a different position
-    "
-    offsets1 keysAndValuesDo:[:varName :varIndex |
-        (offsets2 includesKey:varName) ifFalse:[
-            changeSet add:varName 
-        ] ifTrue:[
-            (varIndex ~~ (offsets2 at:varName)) ifTrue:[
-                changeSet add:varName 
-            ]
-        ]
-    ].
-    offsets2 keysAndValuesDo:[:varName :varIndex |
-        (offsets1 includesKey:varName) ifFalse:[
-            changeSet add:varName
-        ] ifTrue:[
-            (varIndex ~~ (offsets1 at:varName)) ifTrue:[
-                changeSet add:varName
-            ]
-        ]
-    ].
-    ^ changeSet
-
-    "
-     View class 
-        differentInstanceVariableOffsetsIn:View
-                                       and:StandardSystemView
-     View class 
-        differentInstanceVariableOffsetsIn:Object 
-                                       and:Point 
-    "
-!
-
-xx_recompileGlobalAccessorsTo:aGlobalKey in:aNamespace except:someClass
-    "when a new class enters a namespace, all accessors to the same-named
-     class in that namespace must be recompiled"
-
-    aNamespace allPrivateClassesDo:[:aClass |
-        aClass ~~ someClass ifTrue:[
-            aClass isLoaded ifTrue:[
-
-"/                Smalltalk silentLoading ifFalse:[
-"/                    Transcript showCR:'recompiling methods in ''' , aClass name , ''' accessing ''' , aGlobalKey , ''''.
-"/                    Transcript endEntry.
-"/                ].
-
-                aClass recompileMethodsAccessingGlobal:aGlobalKey.
-                aClass class recompileMethodsAccessingGlobal:aGlobalKey.
-                "/ actually - must eventually recompile USERS of this namespace too
-            ]
-        ]
-    ]
-
-    "Modified: 31.1.1997 / 11:22:57 / cg"
-!
-
-xx_recompileMachineCodeMethodsIn:aClass
-    "recompile all machine-code methods in aClass."
-
-    aClass recompileMethodsWithMachineCode.
-    aClass class recompileMethodsWithMachineCode.
 ! !
 
 !Metaclass methodsFor:'queries'!
@@ -1285,6 +504,6 @@
 !Metaclass class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Metaclass.st,v 1.180 2001-10-08 09:17:50 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Metaclass.st,v 1.181 2001-10-08 09:46:53 cg Exp $'
 ! !
 Metaclass initialize!