Skip to content

Commit

Permalink
Make RBAbstractClass match the MOP answering both false by default in…
Browse files Browse the repository at this point in the history
… #isAbstract.

Migrate RBMakeClassAbstractTransformation.
Add data for testing: #RBClassWithoutSelfClassReferenceTest and #RBWithSelfClassReferenceTest
Update RBMakeClassAbstractParametrizedTest
Add #RBMakeClassAbstractDriver with tests
Update #SycCMakeAbstractCommand
  • Loading branch information
Hernán Morales Durand committed Mar 25, 2024
1 parent fe871bc commit 3d5d31f
Show file tree
Hide file tree
Showing 10 changed files with 267 additions and 38 deletions.
5 changes: 3 additions & 2 deletions src/Refactoring-Core/RBAbstractClass.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -504,9 +504,10 @@ RBAbstractClass >> instanceVariableNames: aCollectionOfStrings [

{ #category : 'testing' }
RBAbstractClass >> isAbstract [

(self whichSelectorsReferToSymbol: #subclassResponsibility) ifNotEmpty: [^true].
model allReferencesToClass: self do: [:each | ^false].
^true
model allReferencesToClass: self do: [:each | ^ false].
^ false
]

{ #category : 'testing' }
Expand Down
46 changes: 32 additions & 14 deletions src/Refactoring-Core/RBMakeClassAbstractTransformation.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -20,10 +20,10 @@ RBMakeClassAbstractTransformation class >> basicMenuItemString [
^ 'Make abstract'
]

{ #category : 'instance creation' }
RBMakeClassAbstractTransformation class >> class: targetClass [
{ #category : 'accessing' }
RBMakeClassAbstractTransformation class >> classNamed: aClassName [

^ self new class: targetClass
^ self new classNamed: aClassName
]

{ #category : 'testing' }
Expand All @@ -32,10 +32,34 @@ RBMakeClassAbstractTransformation class >> isTransformation [
^ true
]

{ #category : 'instance creation' }
RBMakeClassAbstractTransformation >> class: class [
{ #category : 'preconditions' }
RBMakeClassAbstractTransformation >> applicabilityPreconditions [
"Answer a <Collection> of <RBCondition>"

^ {
self preconditionHaveNoReferences
}
]

{ #category : 'scripting api - conditions' }
RBMakeClassAbstractTransformation >> checkPreconditions [

targetClass := class
self checkApplicabilityPreconditions
]

{ #category : 'scripting api - conditions' }
RBMakeClassAbstractTransformation >> classNamed: aClassName [

className := aClassName.
targetClass := self model classNamed: aClassName.
]

{ #category : 'preconditions' }
RBMakeClassAbstractTransformation >> preconditionHaveNoReferences [

^ ReClassesHaveNoReferencesCondition new
model: model;
classes: { targetClass }
]

{ #category : 'preconditions' }
Expand All @@ -51,14 +75,8 @@ RBMakeClassAbstractTransformation >> privateTransform [
(RBAddMethodTransformation
sourceCode: 'isAbstract
^ self == ' , targetClass asString
^ self == ' , className
in: targetClass classSide
withProtocol: #testing) execute
]
withProtocol: #testing) execute.

{ #category : 'preconditions' }
RBMakeClassAbstractTransformation >> skippingPreconditions [
"We cannot validate that the class is actually not used and not receiving a message new."

^ (RBCondition isAbstractClass: targetClass) not
]
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
Class {
#name : 'RBClassWithoutSelfClassReferenceTest',
#superclass : 'TestCase',
#category : 'Refactoring-DataForTesting-ForTestRelatedOperation',
#package : 'Refactoring-DataForTesting',
#tag : 'ForTestRelatedOperation'
}
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
Class {
#name : 'RBWithSelfClassReferenceTest',
#superclass : 'TestCase',
#category : 'Refactoring-DataForTesting-ForTestRelatedOperation',
#package : 'Refactoring-DataForTesting',
#tag : 'ForTestRelatedOperation'
}

{ #category : 'testing' }
RBWithSelfClassReferenceTest class >> isAbstract [

^ self == RBWithSelfClassReferenceTest
]

{ #category : 'accessing' }
RBWithSelfClassReferenceTest >> method [

^ RBWithSelfClassReferenceTest
]
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,22 @@ Class {
#tag : 'Parametrized'
}

{ #category : 'helpers' }
RBAbstractRefactoringTest class >> unreferencedClass [
"Answer a <Class> which should not have any references"

| env |
env := (RBNamespace onEnvironment: (RBPackageEnvironment packageName: 'Refactoring-DataForTesting')).
^ env classNamed: self unreferencedClassName
]

{ #category : 'helpers' }
RBAbstractRefactoringTest class >> unreferencedClassName [
"Answer a <Symbol> representing a <Class> which should not have any references"

^ #[82 66 67 108 97 115 115 87 105 116 104 111 117 116 83 101 108 102 67 108 97 115 115 82 101 102 101 114 101 110 99 101 84 101 115 116] asString asSymbol
]

{ #category : 'accessing' }
RBAbstractRefactoringTest >> constructor [
]
Expand Down Expand Up @@ -205,3 +221,10 @@ RBAbstractRefactoringTest >> testConditions [
self assert: (condition not & condition not) check.
self assert: (condition & condition) errorString equals: 'false OR false'
]

{ #category : 'helpers' }
RBAbstractRefactoringTest >> unreferencedClassName [
"Answer a <Symbol> representing a <Class> which should not have any references"

^ self class unreferencedClassName
]
Original file line number Diff line number Diff line change
Expand Up @@ -2,45 +2,59 @@ Class {
#name : 'RBMakeClassAbstractParametrizedTest',
#superclass : 'RBWithDifferentConstructorsParametrizedTest',
#instVars : [
'testClass'
'testClassName'
],
#category : 'Refactoring-Transformations-Tests-SingleParametrized',
#package : 'Refactoring-Transformations-Tests',
#tag : 'SingleParametrized'
}

{ #category : 'tests' }
{ #category : 'building suites' }
RBMakeClassAbstractParametrizedTest class >> testParameters [
^ ParametrizedTestMatrix new
addCase: { #rbClass -> RBMakeClassAbstractTransformation };
addCase: {
#rbClass -> RBMakeClassAbstractTransformation .
#testClassName -> self unreferencedClassName .
#constructor -> #classNamed: };
yourself
]

{ #category : 'running' }
RBMakeClassAbstractParametrizedTest >> setUp [
super setUp.
model := self rbModelForVariableTest.

testClass := RBBasicLintRuleTestData.
testClass class removeSelector: #isAbstract
testClassName := self unreferencedClassName.
testClassName class removeSelector: #isAbstract
]

{ #category : 'running' }
RBMakeClassAbstractParametrizedTest >> tearDown [

testClass class removeSelector: #isAbstract.
(Smalltalk globals at: testClassName) class removeSelector: #isAbstract.
super tearDown
]

{ #category : 'accessing' }
RBMakeClassAbstractParametrizedTest >> testClassName [

^ testClassName
]

{ #category : 'accessing' }
RBMakeClassAbstractParametrizedTest >> testClassName: anObject [

testClassName := anObject
]

{ #category : 'tests' }
RBMakeClassAbstractParametrizedTest >> testMakeClassAbstractAddsIsAbstractMethodToClassSide [
| refactoring |
refactoring := rbClass class: testClass.

| refactoring |
refactoring := self createRefactoringWithArguments: { testClassName }.
self executeRefactoring: refactoring.
self assert: ((refactoring model classNamed: testClass name) classSide
parseTreeForSelector: #isAbstract)
equals: (self parseMethod: 'isAbstract ^self == ', testClass name)
self
assert: ((refactoring model classNamed: testClassName) classSide parseTreeForSelector: #isAbstract)
equals: (self parseMethod: 'isAbstract ^self == ', testClassName)
]

{ #category : 'tests' }
Expand All @@ -51,10 +65,10 @@ RBMakeClassAbstractParametrizedTest >> testMakeClassAbstractPerformChanges [
that check `performChanges` logic."

| refactoring |
refactoring := rbClass class: testClass.
refactoring := self createRefactoringWithArguments: { testClassName }.
self executeRefactoring: refactoring.

refactoring execute.
self assert: ((refactoring model classNamed: testClass name) classSide
parseTreeForSelector: #isAbstract)
equals: (self parseMethod: 'isAbstract ^self == ', testClass name)
self
assert: ((refactoring model classNamed: testClassName) classSide parseTreeForSelector: #isAbstract)
equals: (self parseMethod: 'isAbstract ^self == ', testClassName)
]
90 changes: 90 additions & 0 deletions src/Refactoring-UI-Tests/ReMakeClassAbstractDriverTest.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,90 @@
Class {
#name : 'ReMakeClassAbstractDriverTest',
#superclass : 'ReDriverTest',
#category : 'Refactoring-UI-Tests-Driver',
#package : 'Refactoring-UI-Tests',
#tag : 'Driver'
}

{ #category : 'tests' }
ReMakeClassAbstractDriverTest >> classWithReferenceToAbstract [

^ RBWithSelfClassReferenceTest.
]

{ #category : 'tests' }
ReMakeClassAbstractDriverTest >> classWithoutReferenceToAbstract [

^ Smalltalk globals at: #[82 66 67 108 97 115 115 87 105 116 104 111 117 116 83 101 108 102 67 108 97 115 115 82 101 102 101 114 101 110 99 101 84 101 115 116] asString asSymbol
]

{ #category : 'initialization' }
ReMakeClassAbstractDriverTest >> setUpDriver: driver [

| dialog |
super setUpDriver: driver.
dialog := MockObject new.
dialog
on: #openModal
respond: true.
driver requestDialog: dialog.
]

{ #category : 'running' }
ReMakeClassAbstractDriverTest >> tearDown [

self classWithoutReferenceToAbstract class removeSelector: #isAbstract.
super tearDown.
]

{ #category : 'tests' }
ReMakeClassAbstractDriverTest >> testMakeClassAbstractWhenClassIsReferenced [
"Test making a class abstract when it is referenced"
| driver environment rbClass |

environment := RBClassEnvironment class: self classWithReferenceToAbstract.
driver := RBMakeClassAbstractDriver new
scopes: { environment } class: self classWithReferenceToAbstract;
yourself.

rbClass := driver model classFor: self classWithReferenceToAbstract.

self
deny: rbClass isAbstract
description: 'It tests that the RB class is not abstract because it contains its class reference'.

self setUpDriver: driver.
driver runRefactoring.

self
deny: rbClass isAbstract
description: 'It tests that the RB class is still abstract after applying the refactoring'.
]

{ #category : 'tests' }
ReMakeClassAbstractDriverTest >> testMakeClassAbstractWhenClassNotUsed [
"Test making a class abstract when it is not used anywhere in the system"
| driver environment rbClass |

environment := RBClassEnvironment class: self classWithoutReferenceToAbstract.
driver := RBMakeClassAbstractDriver new
scopes: { environment } class: self classWithoutReferenceToAbstract;
yourself.

rbClass := driver model classFor: self classWithoutReferenceToAbstract.

self
deny: rbClass isAbstract
description: 'It tests that the RB class is not abstract by default'.

self
deny: (self classWithoutReferenceToAbstract canUnderstand: #isAbstract)
description: 'It test that we successfully applied the refactoring which adds #isAbstract to the target class'.

self setUpDriver: driver.
driver runRefactoring.

"It test that we successfully applied the refactoring which adds #isAbstract to the target class"
self assert: driver changes changes anyOne selector equals: #isAbstract.

]
7 changes: 7 additions & 0 deletions src/Refactoring-UI/RBInteractionDriver.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,13 @@ RBInteractionDriver >> initialize [
"for now unused but we should soon use it. Check applyChanges"
]

{ #category : 'accessing' }
RBInteractionDriver >> model [
"Answer the receiver's <RBBrowserEnvironment>"

^ model
]

{ #category : 'accessing' }
RBInteractionDriver >> model: aRBBrowserEnvironment [
model := aRBBrowserEnvironment
Expand Down
46 changes: 46 additions & 0 deletions src/Refactoring-UI/RBMakeClassAbstractDriver.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,46 @@
Class {
#name : 'RBMakeClassAbstractDriver',
#superclass : 'RBInteractionDriver',
#instVars : [
'class'
],
#category : 'Refactoring-UI-Drivers',
#package : 'Refactoring-UI',
#tag : 'Drivers'
}

{ #category : 'execution' }
RBMakeClassAbstractDriver >> changes [
"Remember should not call generateChanges"

refactoring privateTransform.
^ refactoring changes
]

{ #category : 'resources' }
RBMakeClassAbstractDriver >> configureRefactoring [
"Configure the transformation"

refactoring := RBMakeClassAbstractTransformation new
model: model;
classNamed: class name;
yourself.
]

{ #category : 'execution' }
RBMakeClassAbstractDriver >> runRefactoring [
"Run the transformation"

self configureRefactoring.
refactoring failedApplicabilityPreconditions
ifNotEmpty: [ ^ self inform: 'Preconditions not met' ].
self applyChanges.
]

{ #category : 'accessing' }
RBMakeClassAbstractDriver >> scopes: refactoringScopes class: aClass [

scopes := refactoringScopes.
model := self refactoringScopeOn: scopes first.
class := aClass
]
Loading

0 comments on commit 3d5d31f

Please sign in to comment.