Skip to content

Commit

Permalink
Fixes #7342:
Browse files Browse the repository at this point in the history
- first parametrizing slotDefinitionString and slotDefinition
  • Loading branch information
Ducasse committed Sep 20, 2020
1 parent 91fffb0 commit 1031336
Show file tree
Hide file tree
Showing 3 changed files with 34 additions and 17 deletions.
37 changes: 24 additions & 13 deletions src/Kernel/ClassDescription.class.st
Expand Up @@ -1031,21 +1031,32 @@ ClassDescription >> sharedPoolsString [
]

{ #category : #printing }
ClassDescription >> slotDefinitionString [
"Answer a string that contains an executable description of my Slots"
ClassDescription >> slotDefinitionOn: aStream [
"Write on the arg aStream an executable description of my Slots"

| useFull |
aStream nextPutAll: '{ '.
self localSlots
do: [ :slot |
aStream nextPutAll: slot definitionString.
useFull := slot needsFullDefinition ]
separatedBy: [
aStream nextPutAll: ' . '.
useFull ifTrue: [
aStream
cr;
tab;
tab;
tab;
tab ] ].
aStream nextPutAll: ' }'
]

"^self slots ifNotEmpty: [self slots asString] ifEmpty: ['{}']"
{ #category : #printing }
ClassDescription >> slotDefinitionString [
"Answer a string that represents an executable description of my Slots"

^String streamContents: [ :str | | useFull |
str nextPutAll: '{ '.
self localSlots do: [:slot |
str nextPutAll: slot definitionString.
useFull := slot needsFullDefinition]
separatedBy: [
str nextPutAll: ' . '.
useFull ifTrue: [ str cr;tab;tab;tab;tab ]].
str nextPutAll: ' }'. ]

^String streamContents: [ :str | self slotDefinitionOn: str]
]

{ #category : #slots }
Expand Down
6 changes: 3 additions & 3 deletions src/Kernel/InstanceVariableSlot.class.st
Expand Up @@ -36,11 +36,11 @@ InstanceVariableSlot class >> resetIvarSlots [
]

{ #category : #printing }
InstanceVariableSlot >> definitionString [
InstanceVariableSlot >> definitionOn: aStream [
"non special globals are defined by the symbol"
^self needsFullDefinition
ifTrue: [ super definitionString ]
ifFalse: [ self name printString ]
ifTrue: [ super definitionOn: aStream ]
ifFalse: [ self name printOn: aStream ]

]

Expand Down
8 changes: 7 additions & 1 deletion src/Kernel/Slot.class.st
Expand Up @@ -126,10 +126,16 @@ Slot >> definingClass: aClass [
definingClass := aClass
]

{ #category : #printing }
Slot >> definitionOn: aStream [
"Every subclass that adds state must redefine either this method or #printOn:"
^ self printOn: aStream
]

{ #category : #printing }
Slot >> definitionString [
"Every subclass that adds state must redefine either this method or #printOn:"
^ self printString
^ String streamContents: [:s | self definitionOn: s]
]

{ #category : #'code generation' }
Expand Down

0 comments on commit 1031336

Please sign in to comment.