[comp.lang.smalltalk] multiple inheritance bug fixes

colin@pdn.UUCP (Colin Kendall) (02/04/88)

 There are some problems with multiple inheritance in VI2.2.
Here follows a description of the problems, and a  fileIn of some fixes.
The problems have been reported to ParcPlace, but I don't expect 
fixes from them anytime soon. Since we needed to use multiple
inheritance, I developed some temporary fixes which may not be
optimal, but which work. NOTE: the change to Symbol>isInfix causes
an increase of approximately 2% in compile time.  


1. Multiple inheritance problems.


Let M be a class defined as follows:

	Class named: #M
		superclasses: 'A B'
		...

Then:
	
 Problem 1A. If you define a method for M called b, and b is a selector
understood by B, if you subsequently remove b from M, b is no longer
understood by M.

------------------------------------------------------------------------

 Problem 1B. If you redefine M as:

	Class named: #M
		superclasses: 'B A'
		...

   then class A is forgotten as a superclass.

------------------------------------------------------------------------


 Problem 1C. Condense changes destroys all source for multiply-inheriting
classes.

------------------------------------------------------------------------

 Problem 1D. Compound infix selectors

Suppose A defines '=' (or any infix selector), and C defines
'=' with a compound selector,  e.g.:

= anObject
	^self A.= anObject

Suppose further that an instance of C is created, and sent the message
=, as in:

C new = 1


Suppose that  C is then recompiled, e.g. due to adding a new instance
variable. This will result in a SyntaxError:

A.=
	Argument name expected ...
------------------------------------------------------------------------

 Problem 1E.  A copied selector, when removed from the superclass, erroneously
remains in SelectorsOfCopiedMethods (a class variable of Behavior).
 (no fix provided here)


2. Fixes


!SystemDictionary methodsFor: 'system compression'!

condenseChanges
	"Move all the changes onto a compacted sources file.
		Smalltalk condenseChanges."

 " Fixes Problem 1C above"
 "26 January 1988 cmk: using allBehaviorsDo :led to duplicate moves for multiply-inheriting classes, leading to bad pointers"

	| f fileName |
	f _ FileStream fileNamed: 'temp.changes'.
	f timeStamp.
"	Smalltalk allBehaviorsDo: [:class | class moveChangesTo: f]."
 	Object allSubclasses asSet do: [:class | class moveChangesTo: f]. 
	f close.
	f readOnly.
	fileName _ (SourceFiles at: 2) name.
	(SourceFiles at: 2) close.
	SourceFiles at: 2 put: f.
	FileDirectory removeKey: fileName.
	f file rename: fileName! !

!Behavior methodsFor: 'creating method dictionary'!

removeSelector: selector 
	"Assuming that the message selector is in the receiver's method dictionary,
	remove it.  If the selector is not in the method dictionary, create an error
	notification."

 " Part of fix for Problem 1A above"

"1 February 1988 cmk multiple inheritance fix: return the results of self checkMethodFor: (true if no conflict has resulted from the removal)"

	methodDict removeKey: selector.
	self flushCache.
	self checkChangeSelector: selector.
 (self checkMethodFor: selector)ifFalse:[Transcript cr;show: 'inheritance conflict created'. ^false].
^true! !

'From Smalltalk-80, Version 2.2 of July 4, 1987 on 2 February 1988 at 8:55:52 am'!



!Behavior methodsFor: 'creating method dictionary'!

removeSelectorUnchecked: selector 
	"Assuming that the message selector is in the receiver's method dictionary,
	remove it.  If the selector is not in the method dictionary, create an error
	notification.  Do not check for effect on (multiple) inheritance."

"1 February 1988 cmk due to multiple inheritance fixes, we may sometimes call this method when selector is not in methodDict. It's ok, though.  Added ifAbsent:[]"

	methodDict removeKey: selector ifAbsent:[].
	self flushCache! !

'From Smalltalk-80, Version 2.2 of July 4, 1987 on 2 February 1988 at 8:56:31 am'!



!ClassDescription methodsFor: 'method dictionary'!

removeSelector: aSymbol 
	"Remove the message whose selector is aSymbol from the method
	dictionary of the receiver, if it is there.  Answer nil otherwise."

 " Part of fix for Problem 1A above"
"1 February 1988 cmk removal may result in a conflict, or a copy from the non-dynamic chain, or neither (if selector is not implemented in any superclass). If there's a conflict, take different action"

	(methodDict includesKey: aSymbol) ifFalse: [^nil].
"	super removeSelector: aSymbol.
	self organization removeElement: aSymbol."
(super removeSelector: aSymbol)ifTrue:["no conflict"
	self organization removeElement: aSymbol].
	Smalltalk changes removeSelector: aSymbol class: self.
	Smalltalk logChange: self name , ' removeSelector: #' , aSymbol! !

'From Smalltalk-80, Version 2.2 of July 4, 1987 on 2 February 1988 at 9:00:10 am'!



!Metaclass methodsFor: 'class hierarchy'!

name: newName inEnvironment: environ subclassOf: sup and: others instanceVariableNames: instVarString variable: v words: w pointers: p classVariableNames: classVarString poolDictionaries: poolString category: categoryName comment: commentString changed: changed 
	"Create a new metaclass from the information provided in the arguments.
	Create an error if the name does not begin with an uppercase letter or if a
	class of the same name already exists."

 " Fixes Problem 1B above"
"2 February 1988 cmk to avoid errors if order of superclasses is changed, setOtherSuperclasses: others"

	| wasPresent oldClass newClass invalidFields invalidMethods |
	newName first isUppercase
		ifFalse: 
			[self error: 'Class names must be capitalized'.
			^false].
	(wasPresent _ environ includesKey: newName)
		ifTrue: 
			[oldClass _ environ at: newName.
			(oldClass isKindOf: Behavior)
				ifFalse: 
					[self error: newName , ' already exists!!  Proceed will store over it'.
					wasPresent _ false.
					oldClass _ self newNamed: newName otherSupers: others]]
		ifFalse: [  oldClass _ self newNamed: newName otherSupers: others].
	newClass _ oldClass copy.
	invalidFields _ 
		changed | (newClass 
					subclassOf: sup
					oldClass: oldClass
					instanceVariableNames: instVarString
					variable: v
					words: w
					pointers: p
					ifBad: [^false]).
newClass class setOtherSuperclasses: others.
	invalidFields ifFalse: [newClass obsolete.  newClass _ oldClass].
	invalidMethods _ invalidFields | (newClass declare:  classVarString) | (newClass sharing: poolString).
	commentString == nil ifFalse: [newClass comment: commentString].
	(environ includesKey: newName)
		ifFalse: 
			[environ declare: newName from: Undeclared.
			environ at: newName put: newClass].
	SystemOrganization classify: newClass name under: categoryName asSymbol.
	newClass
		validateFrom: oldClass
		in: environ
		instanceVariableNames: invalidFields
		methods: invalidMethods.
	"update subclass lists"
	newClass superclasses do:
		[:newSup | newSup removeSubclass: oldClass; addSubclass: newClass].
	"Update Changes"
	wasPresent
		ifTrue: [Smalltalk changes changeClass: newClass]
		ifFalse: [Smalltalk changes addClass: newClass].
	"Now check for possible conflicting definitions in superclasses"
	invalidFields ifTrue:
		[newClass copyMethods.
		newClass class copyMethods].
	^newClass! !

'From Smalltalk-80, Version 2.2 of July 4, 1987 on 2 February 1988 at 9:00:36 am'!



!Symbol methodsFor: 'system primitives'!

isInfix
	"Answer whether the receiver is an infix message selector."

 " Fixes Problem 1D above"
	"29 January 1988 cmk added check for compound infix selectors - 
	fixes problem with recompilation of copied-down methods in 
	multiply-inheriting classes"

	^(self at: 1) isLetter not or: [self isCompound and: [self selectorPart isInfix]]! !
-- 
Colin Kendall				Paradyne Corporation
{gatech,akgua}!usfvax2!pdn!colin	Mail stop LF-207
Phone: (813) 530-8697			8550 Ulmerton Road, PO Box 2826
					Largo, FL  33294-2826