[Pkg] The Trunk: Kernel-ar.352.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Dec 31 13:17:37 UTC 2009


Andreas Raab uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-ar.352.mcz

==================== Summary ====================

Name: Kernel-ar.352
Author: ar
Time: 29 December 2009, 5:41:30 am
UUID: 090c5c02-8b1a-d34f-a88d-1c203c1ddcfa
Ancestors: Kernel-ar.351

Shipping NanoTraits part 4: Here comes the big clean up. Let's see if it's loadable :-)

=============== Diff against Kernel-ar.351 ===============

Item was changed:
  ----- Method: Class>>category: (in category 'organization') -----
  category: aString 
  	"Categorize the receiver under the system category, aString, removing it from 
  	any previous categorization."
  
  	| oldCategory |
+ 	oldCategory := category.
- 	oldCategory := self basicCategory.
  	aString isString
  		ifTrue: [
+ 			category := aString asSymbol.
+ 			SystemOrganization classify: self name under: category ]
- 			self basicCategory: aString asSymbol.
- 			SystemOrganization classify: self name under: self basicCategory ]
  		ifFalse: [self errorCategoryName].
  	SystemChangeNotifier uniqueInstance
+ 		class: self recategorizedFrom: oldCategory to: category!
- 		class: self recategorizedFrom: oldCategory to: self basicCategory!

Item was changed:
  ----- Method: Behavior>>addSelectorSilently:withMethod: (in category 'adding/removing methods') -----
  addSelectorSilently: selector withMethod: compiledMethod
+ 	self basicAddSelector: selector withMethod: compiledMethod.!
- 	self methodDictAddSelectorSilently: selector withMethod: compiledMethod.
- 	self registerLocalSelector: selector!

Item was changed:
  ----- Method: Class>>category (in category 'organization') -----
  category
  	"Answer the system organization category for the receiver. First check whether the
  	category name stored in the ivar is still correct and only if this fails look it up
  	(latter is much more expensive)"
  
+ 	category ifNotNil: [ :symbol |
- 	| result |
- 	self basicCategory ifNotNil: [ :symbol |
  		((SystemOrganization listAtCategoryNamed: symbol) includes: self name)
  			ifTrue: [ ^symbol ] ].
+ 	category := SystemOrganization categoryOfElement: self name.
+ 	^category!
- 	self basicCategory: (result := SystemOrganization categoryOfElement: self name).
- 	^result!

Item was changed:
  ----- Method: Behavior>>localSelectors (in category 'adding/removing methods') -----
  localSelectors
+ 	"Return a set of selectors defined locally."
+ 	^ self selectors
+ !
- 	"Return a set of selectors defined locally.
- 	The instance variable is lazily initialized. If it is nil then there
- 	are no non-local selectors"
- 
- 	^ self basicLocalSelectors isNil
- 		ifTrue: [self selectors]
- 		ifFalse: [self basicLocalSelectors].!

Item was changed:
  ----- Method: Behavior>>includesLocalSelector: (in category 'testing method dictionary') -----
  includesLocalSelector: aSymbol
+ 	^self includesSelector: aSymbol!
- 	^self basicLocalSelectors isNil
- 		ifTrue: [self includesSelector: aSymbol]
- 		ifFalse: [self localSelectors includes: aSymbol]!

Item was changed:
  ----- Method: Metaclass>>uses:instanceVariableNames: (in category 'initialize-release') -----
  uses: aTraitCompositionOrArray instanceVariableNames: instVarString 
  	| newComposition newMetaClass copyOfOldMetaClass |
  	
  	copyOfOldMetaClass := self copy.
  	newMetaClass := self instanceVariableNames: instVarString.
  	
  	newComposition := aTraitCompositionOrArray asTraitComposition.
- 	newMetaClass assertConsistantCompositionsForNew: newComposition.
  	newMetaClass setTraitComposition: newComposition.
  	
  	SystemChangeNotifier uniqueInstance
  		classDefinitionChangedFrom: copyOfOldMetaClass to: newMetaClass!

Item was removed:
- ----- Method: Behavior>>clearSendCaches (in category 'send caches') -----
- clearSendCaches
- 	LocalSends current clearOut: self!

Item was removed:
- ----- Method: Behavior>>traitComposition (in category 'traits') -----
- traitComposition
- 	self subclassResponsibility!

Item was removed:
- ----- Method: Behavior>>basicLocalSelectors: (in category 'accessing method dictionary') -----
- basicLocalSelectors: aSetOrNil
- 	self subclassResponsibility !

Item was removed:
- ----- Method: Class>>basicLocalSelectors (in category 'accessing') -----
- basicLocalSelectors
- 	"Direct accessor for the instance variable localSelectors.
- 	Since localSelectors is lazily initialized, this may 
- 	return nil, which means that all selectors are local."
- 
- 	^ localSelectors!

Item was removed:
- ----- Method: Behavior>>selfSentSelectorsFromSelectors: (in category 'traits') -----
- selfSentSelectorsFromSelectors: interestingSelectors 
- 	| result |
- 	result := IdentitySet new.
- 	interestingSelectors collect: 
- 			[:sel | 
- 			| m info |
- 			m := self compiledMethodAt: sel ifAbsent: [].
- 			m ifNotNil: 
- 					[info := (SendInfo on: m) collectSends.
- 					info selfSentSelectors do: [:sentSelector | result add: sentSelector]]].
- 	^result!

Item was removed:
- ----- Method: Class>>hasTraitComposition (in category 'accessing') -----
- hasTraitComposition
- 	^traitComposition notNil and:[traitComposition isEmpty not]!

Item was removed:
- ----- Method: Behavior>>updateMethodDictionarySelector: (in category 'traits') -----
- updateMethodDictionarySelector: aSymbol
- 	"A method with selector aSymbol in myself or my traitComposition has been changed.
- 	Do the appropriate update to my methodDict (remove or update method) and
- 	return all affected selectors of me so that my useres get notified."
- 
- 	| modifiedSelectors descriptions |
- 	modifiedSelectors := IdentitySet new.
- 	descriptions := self hasTraitComposition
- 		ifTrue: [ self traitComposition methodDescriptionsForSelector: aSymbol ]
- 		ifFalse: [ #() ].
- 	descriptions do: [:methodDescription | | effectiveMethod selector |
- 		selector := methodDescription selector.
- 		(self includesLocalSelector: selector) ifFalse: [
- 			methodDescription isEmpty
- 				ifTrue: [
- 					self removeTraitSelector: selector.
- 					modifiedSelectors add: selector]
- 				ifFalse: [
- 					effectiveMethod := methodDescription effectiveMethod.
- 					(self compiledMethodAt: selector ifAbsent: [nil]) ~~ effectiveMethod ifTrue: [
- 						self addTraitSelector: selector withMethod: effectiveMethod.
- 						modifiedSelectors add: selector]]]].
- 	^modifiedSelectors!

Item was removed:
- ----- Method: Behavior>>traitOrClassOfSelector: (in category 'traits') -----
- traitOrClassOfSelector: aSymbol
- 	"Return the trait or the class which originally defines the method aSymbol
- 	or return self if locally defined or if it is a conflict marker method.
- 	This is primarly used by Debugger to determin the behavior in which a recompiled
- 	method should be put. If a conflict method is recompiled it should be put into
- 	the class, thus return self. Also see TraitComposition>>traitProvidingSelector:"
- 	
- 	((self includesLocalSelector: aSymbol) or: [
- 		self hasTraitComposition not]) ifTrue: [^self].
- 	^(self traitComposition traitProvidingSelector: aSymbol) ifNil: [self]!

Item was removed:
- ----- Method: Behavior>>deregisterLocalSelector: (in category 'accessing method dictionary') -----
- deregisterLocalSelector: aSymbol
- 	self basicLocalSelectors notNil ifTrue: [
- 		self basicLocalSelectors remove: aSymbol ifAbsent: []]!

Item was removed:
- ----- Method: Behavior>>registerLocalSelector: (in category 'accessing method dictionary') -----
- registerLocalSelector: aSymbol
- 	self basicLocalSelectors notNil ifTrue: [
- 		self basicLocalSelectors add: aSymbol]!

Item was removed:
- ----- Method: Metaclass>>hasTraitComposition (in category 'accessing') -----
- hasTraitComposition
- 	^traitComposition notNil and:[traitComposition isEmpty not]!

Item was removed:
- ----- Method: Behavior>>basicAddTraitSelector:withMethod: (in category 'traits') -----
- basicAddTraitSelector: aSymbol withMethod: aCompiledMethod
- 	"Add aMethod with selector aSymbol to my
- 	methodDict. aMethod must not be defined locally.
- 	Note that I am overridden by ClassDescription
- 	to do a recompilation of the method if it has supersends."
- 
- 	self assert: [(self includesLocalSelector: aSymbol) not].
- 	self ensureLocalSelectors.
- 	self basicAddSelector: aSymbol withMethod: aCompiledMethod.!

Item was removed:
- ----- Method: Behavior>>removeFromComposition: (in category 'traits') -----
- removeFromComposition: aTrait
- 	self setTraitComposition: (self traitComposition copy
- 		removeFromComposition: aTrait)!

Item was removed:
- ----- Method: Behavior>>removeAlias:of: (in category 'traits') -----
- removeAlias: aSymbol of: aTrait
- 	self setTraitComposition: (
- 		self traitComposition copyWithoutAlias: aSymbol of: aTrait)!

Item was removed:
- ----- Method: Metaclass>>noteNewBaseTraitCompositionApplied: (in category 'composition') -----
- noteNewBaseTraitCompositionApplied: aTraitComposition
- 	"The argument is the new trait composition of my base trait - add
- 	the new traits or remove non existing traits on my class side composition.
- 	(Each class trait in my composition has its base trait on the instance side
- 	of the composition - manually added traits to the class side are always 
- 	base traits.)"
- 	
- 	| newComposition traitsFromInstanceSide |
- 	traitsFromInstanceSide := self traitComposition traits
- 		select: [:each | each isClassTrait]
- 		thenCollect: [:each | each baseTrait].
- 		
- 	newComposition := self traitComposition copyTraitExpression.
- 	(traitsFromInstanceSide copyWithoutAll: aTraitComposition traits) do: [:each |
- 		newComposition removeFromComposition: each classTrait].
- 	(aTraitComposition traits copyWithoutAll: traitsFromInstanceSide) do: [:each |
- 		newComposition add:  (each classTrait)].
- 
- 	self setTraitComposition: newComposition!

Item was removed:
- ----- Method: Behavior>>requirements (in category 'send caches') -----
- requirements
- 	^ self requiredSelectorsCache 
- 		ifNil: [#()] 
- 		ifNotNil: [:rsc | rsc requirements]!

Item was removed:
- ----- Method: Class>>basicCategory (in category 'accessing') -----
- basicCategory
- 	^category!

Item was removed:
- ----- Method: Behavior>>traitComposition: (in category 'traits') -----
- traitComposition: aTraitComposition
- 	self subclassResponsibility !

Item was removed:
- ----- Method: Behavior>>isAliasSelector: (in category 'testing method dictionary') -----
- isAliasSelector: aSymbol
- 	"Return true if the selector aSymbol is an alias defined
- 	in my or in another composition somewhere deeper in 
- 	the tree of traits compositions."
- 
- 	^(self includesLocalSelector: aSymbol) not
- 		and: [self hasTraitComposition]
- 		and: [self traitComposition isAliasSelector: aSymbol]!

Item was removed:
- ----- Method: Metaclass>>assertConsistantCompositionsForNew: (in category 'composition') -----
- assertConsistantCompositionsForNew: aTraitComposition
- 	"Applying or modifying a trait composition on the class side
- 	of a behavior has some restrictions."
- 
- 	| baseTraits notAddable message |
- 	baseTraits := aTraitComposition traits select: [:each | each isBaseTrait].
- 	baseTraits isEmpty ifFalse: [
- 		notAddable := (baseTraits reject: [:each | each classSide methodDict isEmpty]).
- 		notAddable isEmpty ifFalse: [
- 			message := String streamContents: [:stream |
- 				stream nextPutAll: 'You can not add the base trait(s)'; cr.
- 				notAddable
- 					do: [:each | stream nextPutAll: each name]
- 					separatedBy: [ stream nextPutAll: ', '].
- 				stream cr; nextPutAll: 'to this composition because it/they define(s) methods on the class side.'].
- 		^TraitCompositionException signal: message]].
- 		
- 	(self instanceSide traitComposition traits asSet =
- 			(aTraitComposition traits
- 				select: [:each | each isClassTrait]
- 				thenCollect: [:each | each baseTrait]) asSet) ifFalse: [
- 				^TraitCompositionException signal: 'You can not add or remove class side traits on
- 				the class side of a composition. (But you can specify aliases or exclusions
- 				for existing traits or add a trait which does not have any methods on the class side.)']!

Item was removed:
- ----- Method: Metaclass>>basicLocalSelectors: (in category 'accessing') -----
- basicLocalSelectors: aSetOrNil
- 	localSelectors := aSetOrNil!

Item was removed:
- ----- Method: Behavior>>isLocalAliasSelector: (in category 'testing method dictionary') -----
- isLocalAliasSelector: aSymbol
- 	"Return true if the selector aSymbol is an alias defined
- 	in my trait composition."
- 
- 	^(self includesLocalSelector: aSymbol) not
- 		and: [self hasTraitComposition]
- 		and: [self traitComposition isLocalAliasSelector: aSymbol]!

Item was removed:
- ----- Method: Behavior>>notifyUsersOfChangedSelector: (in category 'traits') -----
- notifyUsersOfChangedSelector: aSelector
- 	self notifyUsersOfChangedSelectors: (Array with: aSelector)!

Item was removed:
- ----- Method: Behavior>>parseScope (in category 'newcompiler') -----
- parseScope
- 
- 	^ Smalltalk at: #ClassScope ifPresent: [:class | class new class: self]!

Item was removed:
- ----- Method: Behavior>>hasRequiredSelectors (in category 'send caches') -----
- hasRequiredSelectors
- 	^ self requiredSelectors notEmpty!

Item was removed:
- ----- Method: Behavior>>methodDictAddSelectorSilently:withMethod: (in category 'adding/removing methods') -----
- methodDictAddSelectorSilently: selector withMethod: compiledMethod
- 	self basicAddSelector: selector withMethod: compiledMethod!

Item was removed:
- ----- Method: Metaclass>>basicLocalSelectors (in category 'accessing') -----
- basicLocalSelectors
- 	"Direct accessor for the instance variable localSelectors.
- 	Since localSelectors is lazily initialized, this may 
- 	return nil, which means that all selectors are local."
- 
- 	^ localSelectors!

Item was removed:
- ----- Method: Behavior>>purgeLocalSelectors (in category 'traits') -----
- purgeLocalSelectors
- 	self basicLocalSelectors: nil!

Item was removed:
- ----- Method: Behavior>>traitsProvidingSelector: (in category 'traits') -----
- traitsProvidingSelector: aSymbol
- 	| result |
- 	result := OrderedCollection new.
- 	self hasTraitComposition ifFalse: [^result].
- 	(self traitComposition methodDescriptionsForSelector: aSymbol)
- 		do: [:methodDescription | methodDescription selector = aSymbol ifTrue: [
- 			result addAll: (methodDescription locatedMethods
- 				collect: [:each | each location])]].
- 	^result!

Item was removed:
- ----- Method: Behavior>>addTraitSelector:withMethod: (in category 'traits') -----
- addTraitSelector: aSymbol withMethod: aCompiledMethod
- 	self basicAddTraitSelector: aSymbol withMethod: aCompiledMethod.
- 	aCompiledMethod sendsToSuper ifTrue: [
- 		self recompile: aSymbol]!

Item was removed:
- ----- Method: Behavior>>superRequirements (in category 'send caches') -----
- superRequirements
- 	^ self requiredSelectorsCache superRequirements!

Item was removed:
- ----- Method: Behavior>>applyChangesOfNewTraitCompositionReplacing: (in category 'traits') -----
- applyChangesOfNewTraitCompositionReplacing: oldComposition
- 	| changedSelectors |
- 	changedSelectors := self traitComposition
- 		changedSelectorsComparedTo: oldComposition.
- 	changedSelectors isEmpty ifFalse: [
- 		self noteChangedSelectors: changedSelectors].
- 	self traitComposition isEmpty ifTrue: [
- 		self purgeLocalSelectors].
- 	^changedSelectors!

Item was removed:
- ----- Method: Behavior>>isProvidedSelector: (in category 'testing method dictionary') -----
- isProvidedSelector: selector
- 	^ ProvidedSelectors current isSelector: selector providedIn: self
- !

Item was removed:
- ----- Method: Behavior>>notifyUsersOfChangedSelectors: (in category 'traits') -----
- notifyUsersOfChangedSelectors: aCollection!

Item was removed:
- ----- Method: Behavior>>removeTraitSelector: (in category 'traits') -----
- removeTraitSelector: aSymbol
- 	self assert: [(self includesLocalSelector: aSymbol) not].
- 	self basicRemoveSelector: aSymbol!

Item was removed:
- ----- Method: Behavior>>canPerform: (in category 'testing method dictionary') -----
- canPerform: selector
- 	"Answer whether the receiver can safely perform to the message whose selector 
- 	is the argument: it is not an abstract or cancelled method"
- 
- 	^ self classAndMethodFor: selector do: [:c :m | m isProvided] ifAbsent: [false].!

Item was removed:
- ----- Method: Class>>basicCategory: (in category 'accessing') -----
- basicCategory: aSymbol
- 	category := aSymbol!

Item was removed:
- ----- Method: Behavior>>addExclusionOf:to: (in category 'traits') -----
- addExclusionOf: aSymbol to: aTrait
- 	self setTraitComposition: (
- 		self traitComposition copyWithExclusionOf: aSymbol to: aTrait)!

Item was removed:
- ----- Method: Behavior>>basicLocalSelectors (in category 'accessing method dictionary') -----
- basicLocalSelectors
- 	"Direct accessor for the instance variable localSelectors.
- 	Because of hardcoded ivar indexes of Behavior and Class in the VM, Class and
- 	Metaclass declare the needed ivar and override this method as an accessor. 
- 	By returning nil instead of declaring this method as a subclass responsibility,
- 	Behavior can be instantiated for creating anonymous classes."
- 	
- 	^nil!

Item was removed:
- ----- Method: Behavior>>traitTransformations (in category 'traits') -----
- traitTransformations 
- 	^ self traitComposition transformations !

Item was removed:
- ----- Method: Behavior>>hasTraitComposition (in category 'traits') -----
- hasTraitComposition
- 	self subclassResponsibility !

Item was removed:
- ----- Method: Behavior>>sendCaches: (in category 'send caches') -----
- sendCaches: aSendCaches
- 	^ self explicitRequirement!

Item was removed:
- ----- Method: Behavior>>isDisabledSelector: (in category 'testing method dictionary') -----
- isDisabledSelector: selector
- 	^ self classAndMethodFor: selector do: [:c :m | m isDisabled] ifAbsent: [false]!

Item was removed:
- ----- Method: Behavior>>noteChangedSelectors: (in category 'traits') -----
- noteChangedSelectors: aCollection
- 	"Start update of my methodDict (after changes to traits in traitComposition
- 	or after a local method was removed from my methodDict). The argument 
- 	is a collection of method selectors that may have been changed. Most of the time
- 	aCollection only holds one selector. But when there are aliases involved 
- 	there may be several method changes that have to be propagated to users."
- 
- 	| affectedSelectors |
- 	affectedSelectors := IdentitySet new.
- 	aCollection do: [:selector |
- 		affectedSelectors addAll: (self updateMethodDictionarySelector: selector)].
- 	self notifyUsersOfChangedSelectors: affectedSelectors.
- 	^ affectedSelectors!

Item was removed:
- ----- Method: Class>>basicLocalSelectors: (in category 'accessing') -----
- basicLocalSelectors: aSetOrNil
- 	localSelectors := aSetOrNil!

Item was removed:
- ----- Method: Behavior>>ensureLocalSelectors (in category 'traits') -----
- ensureLocalSelectors
- 	"Ensures that the instance variable localSelectors is effectively used to maintain
- 	the set of local selectors.
- 	This method must be called before any non-local selectors are added to the
- 	method dictionary!!"
- 
- 	self basicLocalSelectors isNil 
- 		ifTrue: [self basicLocalSelectors: self selectors asSet]!

Item was removed:
- ----- Method: Behavior>>addToComposition: (in category 'traits') -----
- addToComposition: aTrait
- 	self setTraitComposition: (self traitComposition copyTraitExpression
- 		add: aTrait;
- 		yourself)!

Item was removed:
- ----- Method: Behavior>>setRequiredStatusOf:to: (in category 'send caches') -----
- setRequiredStatusOf: selector to: aBoolean
- 	aBoolean 
- 		ifTrue: [self requiredSelectorsCache addRequirement: selector]
- 		ifFalse: [self requiredSelectorsCache removeRequirement: selector].!

Item was removed:
- ----- Method: Behavior>>traitCompositionString (in category 'traits') -----
- traitCompositionString
- 	^self hasTraitComposition
- 		ifTrue: [self traitComposition asString]
- 		ifFalse: ['{}']!

Item was removed:
- ----- Method: Behavior>>traitCompositionIncludes: (in category 'traits') -----
- traitCompositionIncludes: aTrait
- 	^self == aTrait or: 
- 		[self hasTraitComposition and: 
- 			[self traitComposition allTraits includes: aTrait]]!

Item was removed:
- ----- Method: Behavior>>setTraitCompositionFrom: (in category 'traits') -----
- setTraitCompositionFrom: aTraitExpression
- 	^ self setTraitComposition: aTraitExpression asTraitComposition!



More information about the Packages mailing list