Skip to content

Commit

Permalink
using oldDefinition
Browse files Browse the repository at this point in the history
  • Loading branch information
estebanlm committed May 24, 2019
1 parent 1e2f183 commit 9c5cf40
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 3 deletions.
3 changes: 2 additions & 1 deletion src/System-Changes/ChangeSet.class.st
Expand Up @@ -800,7 +800,8 @@ ChangeSet >> expungeEmptyClassChangeEntries [
ChangeSet >> fatDefForClass: class [
| newDef oldDef oldStrm newStrm outStrm oldVars newVars addedVars |
class isBehavior ifFalse: [ ^ class definition ].
newDef := class definition.

newDef := class oldDefinition.
oldDef := (self changeRecorderFor: class) priorDefinition.
oldDef ifNil: [ ^ newDef ].
oldDef = newDef ifTrue: [ ^ newDef ].
Expand Down
4 changes: 2 additions & 2 deletions src/Tests/ChangeSetClassChangesTest.class.st
Expand Up @@ -165,7 +165,7 @@ ChangeSetClassChangesTest >> testChangeClassCategory [
classVariableNames: ''
poolDictionaries: ''
category: 'DeleteMe-1'.
saveClassDefinition := (Smalltalk globals classNamed: #JunkClass) definition.
saveClassDefinition := (Smalltalk globals classNamed: #JunkClass) oldDefinition.
self assert: saveClassDefinition = (ChangeSet current fatDefForClass: (Smalltalk globals classNamed: #JunkClass)). "Redefine the class, changing only the class category"
Object
subclass: #JunkClass
Expand All @@ -182,7 +182,7 @@ ChangeSetClassChangesTest >> testChangeClassCategory [
self
assert:
(self
isDefinition: (Smalltalk globals classNamed: #JunkClass) definition
isDefinition: (Smalltalk globals classNamed: #JunkClass) oldDefinition
equivalentTo: (ChangeSet current fatDefForClass: (Smalltalk globals classNamed: #JunkClass))). "Assert that the change has been recorded in the current change set"
self
assert:
Expand Down

0 comments on commit 9c5cf40

Please sign in to comment.