From a152c0e917c02281605e5e479a0562c8ed5d2511 Mon Sep 17 00:00:00 2001 From: Denis Kudriashov Date: Fri, 24 Nov 2017 18:06:34 +0100 Subject: [PATCH] definingClass is added to Slot. It is initialized in ClassDescription>>superclass:layout: SlotIntegrationTest>>testSlotsAreInitializedWithDefiningAnonimousClass covers that initialization is performed. --- src/Kernel/ClassDescription.class.st | 14 -------------- src/Slot-Tests/SlotIntegrationTest.class.st | 15 +++++++++++++++ src/Slot/Behavior.extension.st | 14 ++++++++++++++ src/Slot/ClassDescription.extension.st | 1 + src/Slot/Slot.class.st | 12 ++++++++---- 5 files changed, 38 insertions(+), 18 deletions(-) diff --git a/src/Kernel/ClassDescription.class.st b/src/Kernel/ClassDescription.class.st index 36c97ca262c..973aac84da7 100644 --- a/src/Kernel/ClassDescription.class.st +++ b/src/Kernel/ClassDescription.class.st @@ -587,20 +587,6 @@ ClassDescription >> copyMethodDictionaryFrom: donorClass [ self organization: donorClass organization deepCopy. ] -{ #category : #slots } -ClassDescription >> definesSlot: aSlot [ - "Return true whether the receiver defines an instance variable named aString" - - ^ self slots identityIncludes: aSlot -] - -{ #category : #slots } -ClassDescription >> definesSlotNamed: aString [ - "Return true whether the receiver defines an instance variable named aString." - - ^ self slotNames includes: aString -] - { #category : #'filein/out' } ClassDescription >> definition [ "Answer a String that defines the receiver." diff --git a/src/Slot-Tests/SlotIntegrationTest.class.st b/src/Slot-Tests/SlotIntegrationTest.class.st index 4b0ce85da8c..bf588995de2 100644 --- a/src/Slot-Tests/SlotIntegrationTest.class.st +++ b/src/Slot-Tests/SlotIntegrationTest.class.st @@ -415,6 +415,21 @@ SlotIntegrationTest >> testSlotScopeParallelism [ self assert: classWithWrongSlotScope asArray equals: #() ] +{ #category : #tests } +SlotIntegrationTest >> testSlotsAreInitializedWithDefiningAnonimousClass [ + "All slots should include reference to defining class" + aClass := self make: [ :builder | + builder + name: self aClassName; + slots: #(x) + ]. + self assert: aClass slots first definingClass equals: aClass. + + aClass addInstVarNamed: 'y'. + self assert: aClass slots size equals: 2. + self assert: (aClass slots collect: #definingClass as: Set) equals: {aClass} asSet +] + { #category : #tests } SlotIntegrationTest >> testSmallIntegerLayout [ self assert: (SmallInteger classLayout isKindOf: ImmediateLayout). diff --git a/src/Slot/Behavior.extension.st b/src/Slot/Behavior.extension.st index 73392d6df06..f62a9b733d4 100644 --- a/src/Slot/Behavior.extension.st +++ b/src/Slot/Behavior.extension.st @@ -14,3 +14,17 @@ Behavior >> classLayout [ Behavior >> classLayout: aClassLayout [ layout := aClassLayout ] + +{ #category : #'*Slot' } +Behavior >> definesSlot: aSlot [ + "Return true whether the receiver defines an instance variable named aString" + + ^ self slots identityIncludes: aSlot +] + +{ #category : #'*Slot' } +Behavior >> definesSlotNamed: aString [ + "Return true whether the receiver defines an instance variable named aString." + + ^ self slotNames includes: aString +] diff --git a/src/Slot/ClassDescription.extension.st b/src/Slot/ClassDescription.extension.st index 3aba042ff32..a729ce8c543 100644 --- a/src/Slot/ClassDescription.extension.st +++ b/src/Slot/ClassDescription.extension.st @@ -3,6 +3,7 @@ Extension { #name : #ClassDescription } { #category : #'*Slot' } ClassDescription >> superclass: aSuperclass layout: aLayout [ layout := aLayout. + layout slots do: [ :each | each definingClass: self ]. self superclass: aSuperclass diff --git a/src/Slot/Slot.class.st b/src/Slot/Slot.class.st index 1abedf05de1..73edf65c9c4 100644 --- a/src/Slot/Slot.class.st +++ b/src/Slot/Slot.class.st @@ -14,7 +14,8 @@ Class { #name : #Slot, #superclass : #Object, #instVars : [ - 'name' + 'name', + 'definingClass' ], #classVars : [ 'Properties' @@ -113,9 +114,12 @@ Slot >> changingIn: aClass [ { #category : #queries } Slot >> definingClass [ - ^(Smalltalk globals allClasses flatCollect: [:each | {each . each classSide} ]) - detect: [ :class | class classLayout definesSlot: self] - ifNone: [ nil ] + ^definingClass +] + +{ #category : #queries } +Slot >> definingClass: aClass [ + definingClass := aClass ] { #category : #printing }